home *** CD-ROM | disk | FTP | other *** search
Text File | 2000-08-22 | 9.4 MB | 20 lines | [STch/FAST] |
Text Truncated. Only the first 1MB is shown below. Download the file for the complete contents.
- 'From Squeak2.8 of 13 June 2000 [latest update: #2356] on 16 August 2000 at 7:43:20 pm'!This is a simple ADPCM (adapative delta pulse code modulation) codec. This is a general audio codec that compresses speech, music, or sound effects equally well, and works at any sampling rate (i.e., it contains no frequency-sensitive filters). It compresses 16-bit sample data down to 5, 4, 3, or 2 bits per sample, with lower fidelity and increased noise at the lowest bit rates. Although it does not deliver state-of-the-art compressions, the alorithm is small, simple, and extremely fast, since the encode/decode primitives have been translated into C primitives.This codec will also encode and decode all Flash .swf file compressed sound formats, both mono and stereo. (Note: stereo Flash compression is not yet implemented, but stereo decompression works.)!!ADPCMCodec methodsFor: 'bit streaming' stamp: 'jm 3/28/1999 16:24'!nextBits: n "Answer the next n bits of my bit stream as an unsigned integer." | result remaining shift | self inline: true. result _ 0. remaining _ n. [true] whileTrue: [ shift _ remaining - bitPosition. result _ result + (currentByte bitShift: shift). shift > 0 ifTrue: [ "consumed currentByte buffer; fetch next byte" remaining _ remaining - bitPosition. currentByte _ (encodedBytes at: (byteIndex _ byteIndex + 1)). bitPosition _ 8] ifFalse: [ "still some bits left in currentByte buffer" bitPosition _ bitPosition - remaining. "mask out the consumed bits:" currentByte _ currentByte bitAnd: (255 bitShift: (bitPosition - 8)). ^ result]].! !!ADPCMCodec methodsFor: 'bit streaming' stamp: 'jm 3/28/1999 20:21'!nextBits: n put: anInteger "Write the next n bits to my bit stream." | buf bufBits bitsAvailable shift | self inline: true. buf _ anInteger. bufBits _ n. [true] whileTrue: [ bitsAvailable _ 8 - bitPosition. shift _ bitsAvailable - bufBits. "either left or right shift" "append high bits of buf to end of currentByte:" currentByte _ currentByte + (buf bitShift: shift). shift < 0 ifTrue: [ "currentByte buffer filled; output it" encodedBytes at: (byteIndex _ byteIndex + 1) put: currentByte. bitPosition _ 0. currentByte _ 0. "clear saved high bits of buf:" buf _ buf bitAnd: (1 bitShift: 0 - shift) - 1. bufBits _ bufBits - bitsAvailable] ifFalse: [ "still some bits available in currentByte buffer" bitPosition _ bitPosition + bufBits. ^ self]].! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 3/27/1999 11:21'!bytesPerEncodedFrame "Answer the number of bytes required to hold one frame of compressed sound data." "Note: When used as a normal codec, the frame size is always 8 samples which results in (8 * bitsPerSample) / 8 = bitsPerSample bytes." ^ bitsPerSample! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 7/2/1999 13:29'!compressAndDecompress: aSound "Compress and decompress the given sound. Overridden to use same bits per sample for both compressing and decompressing." | compressed decoder | compressed _ self compressSound: aSound. decoder _ self class new initializeForBitsPerSample: bitsPerSample samplesPerFrame: 0. ^ decoder decompressSound: compressed! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 3/28/1999 15:37'!decodeFrames: frameCount from: srcByteArray at: srcIndex into: dstSoundBuffer at: dstIndex "Decode the given number of monophonic frames starting at the given index in the given ByteArray of compressed sound data and storing the decoded samples into the given SoundBuffer starting at the given destination index. Answer a pair containing the number of bytes of compressed data consumed and the number of decompressed samples produced." "Note: Assume that the sender has ensured that the given number of frames will not exhaust either the source or destination buffers." encodedBytes _ srcByteArray. byteIndex _ srcIndex - 1. bitPosition _ 0. currentByte _ 0. samples _ dstSoundBuffer. sampleIndex _ dstIndex - 1. self privateDecodeMono: (frameCount * self samplesPerFrame). ^ Array with: (byteIndex - (srcIndex - 1)) with: (sampleIndex - (dstIndex - 1))! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 3/28/1999 15:28'!encodeFrames: frameCount from: srcSoundBuffer at: srcIndex into: dstByteArray at: dstIndex "Encode the given number of frames starting at the given index in the given monophonic SoundBuffer and storing the encoded sound data into the given ByteArray starting at the given destination index. Encode only as many complete frames as will fit into the destination. Answer a pair containing the number of samples consumed and the number of bytes of compressed data produced." "Note: Assume that the sender has ensured that the given number of frames will not exhaust either the source or destination buffers." samples _ srcSoundBuffer. sampleIndex _ srcIndex - 1. encodedBytes _ dstByteArray. byteIndex _ dstIndex - 1. bitPosition _ 0. currentByte _ 0. self privateEncodeMono: (frameCount * self samplesPerFrame). ^ Array with: frameCount with: (byteIndex - (dstIndex - 1))! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 3/28/1999 20:12'!resetForMono "Reset my encoding and decoding state for mono." predicted _ 0. index _ 0.! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 3/28/1999 20:12'!resetForStereo "Reset my encoding and decoding state for stereo." "keep state as SoundBuffers to allow fast access from primitive" predicted _ SoundBuffer new: 2. index _ SoundBuffer new: 2.! !!ADPCMCodec methodsFor: 'codec stuff' stamp: 'jm 3/27/1999 08:34'!samplesPerFrame "Answer the number of sound samples per compression frame." frameSizeMask > 0 ifTrue: [^ frameSizeMask + 1]. ^ 8 "frame size when there are no running headers"! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 06:26'!decode: aByteArray bitsPerSample: bits ^ self decode: aByteArray sampleCount: (aByteArray size * 8) // bits bitsPerSample: bits frameSize: 0 stereo: false! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 15:57'!decode: aByteArray sampleCount: count bitsPerSample: bits frameSize: frameSize stereo: stereoFlag self initializeForBitsPerSample: bits samplesPerFrame: frameSize. encodedBytes _ aByteArray. byteIndex _ 0. bitPosition _ 0. currentByte _ 0. stereoFlag ifTrue: [ self resetForStereo. samples _ SoundBuffer newMonoSampleCount: count. rightSamples _ SoundBuffer newMonoSampleCount: count. sampleIndex _ 0. self privateDecodeStereo: count. ^ Array with: samples with: rightSamples] ifFalse: [ samples _ SoundBuffer newMonoSampleCount: count. sampleIndex _ 0. self privateDecodeMono: count. ^ samples]! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/30/1999 08:56'!decodeFlash: aByteArray sampleCount: sampleCount stereo: stereoFlag | bits | encodedBytes _ aByteArray. byteIndex _ 0. bitPosition _ 0. currentByte _ 0. bits _ 2 + (self nextBits: 2). "bits per sample" self initializeForBitsPerSample: bits samplesPerFrame: 4096. stereoFlag ifTrue: [ self resetForStereo. samples _ SoundBuffer newMonoSampleCount: sampleCount. rightSamples _ SoundBuffer newMonoSampleCount: sampleCount. sampleIndex _ 0. self privateDecodeStereo: sampleCount. ^ Array with: samples with: rightSamples] ifFalse: [ samples _ SoundBuffer newMonoSampleCount: sampleCount. sampleIndex _ 0. self privateDecodeMono: sampleCount. ^ Array with: samples].! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 08:59'!encode: aSoundBuffer bitsPerSample: bits ^ self encodeLeft: aSoundBuffer right: nil bitsPerSample: bits frameSize: 0 forFlash: false! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 08:58'!encodeFlashLeft: leftSoundBuffer right: rightSoundBuffer bitsPerSample: bits ^ self encodeLeft: leftSoundBuffer right: rightSoundBuffer bitsPerSample: bits frameSize: 4096 forFlash: true! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 09:17'!encodeLeft: leftSoundBuffer right: rightSoundBuffer bitsPerSample: bits frameSize: frameSize forFlash: flashFlag | stereoFlag sampleCount sampleBitCount bitCount | self initializeForBitsPerSample: bits samplesPerFrame: frameSize. stereoFlag _ rightSoundBuffer notNil. sampleCount _ leftSoundBuffer monoSampleCount. stereoFlag ifTrue: [sampleBitCount _ 2 * (sampleCount * bitsPerSample)] ifFalse: [sampleBitCount _ sampleCount * bitsPerSample]. bitCount _ sampleBitCount + (self headerBitsForSampleCount: sampleCount stereoFlag: stereoFlag). encodedBytes _ ByteArray new: (bitCount / 8) ceiling. byteIndex _ 0. bitPosition _ 0. currentByte _ 0. flashFlag ifTrue: [self nextBits: 2 put: bits - 2]. stereoFlag ifTrue: [ samples _ Array with: leftSoundBuffer with: rightSoundBuffer. sampleIndex _ Array with: 0 with: 0. self privateEncodeStereo: sampleCount] ifFalse: [ samples _ leftSoundBuffer. sampleIndex _ 0. self privateEncodeMono: sampleCount]. ^ encodedBytes! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/27/1999 12:14'!headerBitsForSampleCount: sampleCount stereoFlag: stereoFlag "Answer the number of extra header bits required for the given number of samples. This will be zero if I am not using frame headers." | frameCount bitsPerHeader | frameSizeMask = 0 ifTrue: [^ 0]. frameCount _ (sampleCount / self samplesPerFrame) ceiling. bitsPerHeader _ 16 + 6. stereoFlag ifTrue: [bitsPerHeader _ 2 * bitsPerHeader]. ^ frameCount * bitsPerHeader! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 16:08'!indexForDeltaFrom: thisSample to: nextSample "Answer the best index to use for the difference between the given samples." "Details: Scan stepSizeTable for the first entry >= the absolute value of the difference between sample values. Since indexes are zero-based, the index used during decoding will be the one in the following stepSizeTable entry. Since the index field of a Flash frame header is only six bits, the maximum index value is 63." "Note: Since there does not appear to be any documentation of how Flash acutally computes the indices used in its frame headers, this algorithm was guessed by reverse-engineering the Flash ADPCM decoder." | diff bestIndex | self inline: true. diff _ nextSample - thisSample. diff < 0 ifTrue: [diff _ 0 - diff]. bestIndex _ 63. 1 to: 62 do: [:j | bestIndex = 63 ifTrue: [ (stepSizeTable at: j) >= diff ifTrue: [bestIndex _ j]]]. ^ bestIndex! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/28/1999 20:48'!initializeForBitsPerSample: sampleBits samplesPerFrame: frameSize self resetForMono. stepSizeTable _ #(7 8 9 10 11 12 13 14 16 17 19 21 23 25 28 31 34 37 41 45 50 55 60 66 73 80 88 97 107 118 130 143 157 173 190 209 230 253 279 307 337 371 408 449 494 544 598 658 724 796 876 963 1060 1166 1282 1411 1552 1707 1878 2066 2272 2499 2749 3024 3327 3660 4026 4428 4871 5358 5894 6484 7132 7845 8630 9493 10442 11487 12635 13899 15289 16818 18500 20350 22385 24623 27086 29794 32767). indexTable _ nil. sampleBits = 2 ifTrue: [ indexTable _ #(-1 2)]. sampleBits = 3 ifTrue: [ indexTable _ #(-1 -1 2 4)]. sampleBits = 4 ifTrue: [ indexTable _ #(-1 -1 -1 -1 2 4 6 8)]. sampleBits = 5 ifTrue: [ indexTable _ #(-1 -1 -1 -1 -1 -1 -1 -1 1 2 4 6 8 10 13 16)]. indexTable ifNil: [self error: 'unimplemented bits/sample']. bitsPerSample _ sampleBits. deltaSignMask _ 1 bitShift: bitsPerSample - 1. deltaValueMask _ deltaSignMask - 1. deltaValueHighBit _ deltaSignMask / 2. frameSize <= 1 ifTrue: [frameSizeMask _ 0] ifFalse: [ (frameSize = (1 bitShift: frameSize highBit - 1)) ifFalse: [self error: 'frameSize must be a power of two']. frameSizeMask _ frameSize - 1]. "keep as SoundBuffer to allow fast access from primitive" indexTable _ SoundBuffer fromArray: indexTable. stepSizeTable _ SoundBuffer fromArray: stepSizeTable.! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/29/1999 07:13'!privateDecodeMono: count | delta step predictedDelta bit | <primitive: 550> self var: #stepSizeTable declareC: 'short int *stepSizeTable'. self var: #indexTable declareC: 'short int *indexTable'. self var: #samples declareC: 'short int *samples'. self var: #encodedBytes declareC: 'unsigned char *encodedBytes'. 1 to: count do: [:i | (i bitAnd: frameSizeMask) = 1 ifTrue: [ "start of frame; read frame header" predicted _ self nextBits: 16. predicted > 32767 ifTrue: [predicted _ predicted - 65536]. index _ self nextBits: 6. samples at: (sampleIndex _ sampleIndex + 1) put: predicted] ifFalse: [ delta _ self nextBits: bitsPerSample. step _ stepSizeTable at: index + 1. predictedDelta _ 0. bit _ deltaValueHighBit. [bit > 0] whileTrue: [ (delta bitAnd: bit) > 0 ifTrue: [predictedDelta _ predictedDelta + step]. step _ step bitShift: -1. bit _ bit bitShift: -1]. predictedDelta _ predictedDelta + step. (delta bitAnd: deltaSignMask) > 0 ifTrue: [predicted _ predicted - predictedDelta] ifFalse: [predicted _ predicted + predictedDelta]. predicted > 32767 ifTrue: [predicted _ 32767] ifFalse: [predicted < -32768 ifTrue: [predicted _ -32768]]. index _ index + (indexTable at: (delta bitAnd: deltaValueMask) + 1). index < 0 ifTrue: [index _ 0] ifFalse: [index > 88 ifTrue: [index _ 88]]. samples at: (sampleIndex _ sampleIndex + 1) put: predicted]].! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/29/1999 07:13'!privateDecodeStereo: count | predictedLeft predictedRight indexLeft indexRight deltaLeft deltaRight stepLeft stepRight predictedDeltaLeft predictedDeltaRight bit | <primitive: 551> self var: #stepSizeTable declareC: 'short int *stepSizeTable'. self var: #indexTable declareC: 'short int *indexTable'. self var: #samples declareC: 'short int *samples'. self var: #encodedBytes declareC: 'unsigned char *encodedBytes'. self var: #rightSamples declareC: 'short int *rightSamples'. self var: #predicted declareC: 'short int *predicted'. self var: #index declareC: 'short int *index'. "make local copies of decoder state variables" predictedLeft _ predicted at: 1. predictedRight _ predicted at: 2. indexLeft _ index at: 1. indexRight _ index at: 2. 1 to: count do: [:i | (i bitAnd: frameSizeMask) = 1 ifTrue: [ "start of frame; read frame header" predictedLeft _ self nextBits: 16. indexLeft _ self nextBits: 6. predictedRight _ self nextBits: 16. indexRight _ self nextBits: 6. predictedLeft > 32767 ifTrue: [predictedLeft _ predictedLeft - 65536]. predictedRight > 32767 ifTrue: [predictedRight _ predictedRight - 65536]. samples at: (sampleIndex _ sampleIndex + 1) put: predictedLeft. rightSamples at: sampleIndex put: predictedRight] ifFalse: [ deltaLeft _ self nextBits: bitsPerSample. deltaRight _ self nextBits: bitsPerSample. stepLeft _ stepSizeTable at: indexLeft + 1. stepRight _ stepSizeTable at: indexRight + 1. predictedDeltaLeft _ predictedDeltaRight _ 0. bit _ deltaValueHighBit. [bit > 0] whileTrue: [ (deltaLeft bitAnd: bit) > 0 ifTrue: [ predictedDeltaLeft _ predictedDeltaLeft + stepLeft]. (deltaRight bitAnd: bit) > 0 ifTrue: [ predictedDeltaRight _ predictedDeltaRight + stepRight]. stepLeft _ stepLeft bitShift: -1. stepRight _ stepRight bitShift: -1. bit _ bit bitShift: -1]. predictedDeltaLeft _ predictedDeltaLeft + stepLeft. predictedDeltaRight _ predictedDeltaRight + stepRight. (deltaLeft bitAnd: deltaSignMask) > 0 ifTrue: [predictedLeft _ predictedLeft - predictedDeltaLeft] ifFalse: [predictedLeft _ predictedLeft + predictedDeltaLeft]. (deltaRight bitAnd: deltaSignMask) > 0 ifTrue: [predictedRight _ predictedRight - predictedDeltaRight] ifFalse: [predictedRight _ predictedRight + predictedDeltaRight]. predictedLeft > 32767 ifTrue: [predictedLeft _ 32767] ifFalse: [predictedLeft < -32768 ifTrue: [predictedLeft _ -32768]]. predictedRight > 32767 ifTrue: [predictedRight _ 32767] ifFalse: [predictedRight < -32768 ifTrue: [predictedRight _ -32768]]. indexLeft _ indexLeft + (indexTable at: (deltaLeft bitAnd: deltaValueMask) + 1). indexLeft < 0 ifTrue: [indexLeft _ 0] ifFalse: [indexLeft > 88 ifTrue: [indexLeft _ 88]]. indexRight _ indexRight + (indexTable at: (deltaRight bitAnd: deltaValueMask) + 1). indexRight < 0 ifTrue: [indexRight _ 0] ifFalse: [indexRight > 88 ifTrue: [indexRight _ 88]]. samples at: (sampleIndex _ sampleIndex + 1) put: predictedLeft. rightSamples at: sampleIndex put: predictedRight]]. "save local copies of decoder state variables" predicted at: 1 put: predictedLeft. predicted at: 2 put: predictedRight. index at: 1 put: indexLeft. index at: 2 put: indexRight.! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/29/1999 07:13'!privateEncodeMono: count | step sign diff delta predictedDelta bit p | <primitive: 552> self var: #stepSizeTable declareC: 'short int *stepSizeTable'. self var: #indexTable declareC: 'short int *indexTable'. self var: #samples declareC: 'short int *samples'. self var: #encodedBytes declareC: 'unsigned char *encodedBytes'. step _ stepSizeTable at: 1. 1 to: count do: [:i | (i bitAnd: frameSizeMask) = 1 ifTrue: [ predicted _ samples at: (sampleIndex _ sampleIndex + 1). (p _ predicted) < 0 ifTrue: [p _ p + 65536]. self nextBits: 16 put: p. i < count ifTrue: [ index _ self indexForDeltaFrom: predicted to: (samples at: sampleIndex + 1)]. self nextBits: 6 put: index. ] ifFalse: [ "compute sign and magnitude of difference from the predicted sample" sign _ 0. diff _ (samples at: (sampleIndex _ sampleIndex + 1)) - predicted. diff < 0 ifTrue: [ sign _ deltaSignMask. diff _ 0 - diff]. "Compute encoded delta and the difference that this will cause in the predicted sample value during decoding. Note that this code approximates: delta _ (4 * diff) / step. predictedDelta _ ((delta + 0.5) * step) / 4; but in the shift step bits are dropped. Thus, even if you have fast mul/div hardware you cannot use it since you would get slightly different bits what than the algorithm defines." delta _ 0. predictedDelta _ 0. bit _ deltaValueHighBit. [bit > 0] whileTrue: [ diff >= step ifTrue: [ delta _ delta + bit. predictedDelta _ predictedDelta + step. diff _ diff - step]. step _ step bitShift: -1. bit _ bit bitShift: -1]. predictedDelta _ predictedDelta + step. "compute and clamp new prediction" sign > 0 ifTrue: [predicted _ predicted - predictedDelta] ifFalse: [predicted _ predicted + predictedDelta]. predicted > 32767 ifTrue: [predicted _ 32767] ifFalse: [predicted < -32768 ifTrue: [predicted _ -32768]]. "compute new index and step values" index _ index + (indexTable at: delta + 1). index < 0 ifTrue: [index _ 0] ifFalse: [index > 88 ifTrue: [index _ 88]]. step _ stepSizeTable at: index + 1. "output encoded, signed delta" self nextBits: bitsPerSample put: (sign bitOr: delta)]]. bitPosition > 0 ifTrue: [ "flush the last output byte, if necessary" encodedBytes at: (byteIndex _ byteIndex + 1) put: currentByte].! !!ADPCMCodec methodsFor: 'as yet unclassified' stamp: 'jm 3/29/1999 07:14'!privateEncodeStereo: count <primitive: 553> "not yet implemented" self inline: false. self success: false.! !!ADPCMCodec class methodsFor: 'instance creation' stamp: 'jm 3/27/1999 11:15'!new ^ super new initializeForBitsPerSample: 4 samplesPerFrame: 0.! !!ADPCMCodec class methodsFor: 'primitive generation' stamp: 'jm 3/28/1999 21:03'!cCodeForPrimitives "Answer a string containing the translated C code for my primitives." "Note: This code currently must be hand-edited to remove several methods that are inlined (thus not needed) but not pruned out by the ST-to-C translator." ^ CCodeGenerator new codeStringForPrimitives: #( (ADPCMCodec privateDecodeMono:) (ADPCMCodec privateDecodeStereo:) (ADPCMCodec privateEncodeMono:) (ADPCMCodec privateEncodeStereo:) (ADPCMCodec indexForDeltaFrom:to:) (ADPCMCodec nextBits:) (ADPCMCodec nextBits:put:))! !I represent an Apple Event Descriptor. I am a low-level representation of Apple Event (and hence Applescript) information. For further Information, see Apple's Inside Macintosh: Interapplication Communications, at http://developer.apple.com/techpubs/mac/IAC/IAC-2.html.Essentially, I represent a record comprising a one-word "string" (treating the word as fourbyte characters) representing a data type, followed by a pointer to a pointer (a handle) to the data I represent. Care must be taken to assure that the Handle data is disposed after use, or memory leaks result. At this time, I make no effort to do this automatically through finalization.!]style[(218 54 384)f1,f1Rhttp://developer.apple.com/techpubs/mac/IAC/IAC-2.html;,f1!!AEDesc methodsFor: 'accessing' stamp: 'acg 9/12/1999 21:33'!dataSize ^self handleSizeAt: 2! !!AEDesc methodsFor: 'accessing' stamp: 'acg 9/20/1999 14:22'!dispose (0 = (self at: 2)) ifTrue: [self error: 'cannot dispose of unallocated space']. self primAEDisposeDesc isZero ifFalse: [self error: 'dispose operation failed']. self at: 1 put: 0. self at: 2 put: 0. ^nil! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/24/1999 00:35'!asCompiledApplescript | theSize | ((self at: 1) ~= 16r73637074) ifTrue: [^self error: 'AEDesc is not of type ''scpt''']. (theSize _ self dataSize) < 0 ifTrue: [^self error: 'Invalid size for data']. ^self primAEDescToString: (CompiledApplescript new: theSize).! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/24/1999 00:31'!asCompiledApplescriptThenDispose | CAD | CAD _ self asCompiledApplescript. self dispose. ^CAD! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/26/1999 18:39'!asOSAIDThenDisposeAEDescWith: aComponent ^aComponent loadAndDisposeAEDesc: self mode: 0! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/23/1999 23:46'!asShort ^(self primAEDescToString: (ByteArray new: 2)) shortAt: 1 bigEndian: true! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/23/1999 23:47'!asShortThenDispose | short | short _ self asShort. self dispose. ^short! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/20/1999 14:19'!asString | theSize | ((self at: 1) ~= 16r54455854) ifTrue: [^self error: 'AEDesc is not of type ''TEXT''']. (theSize _ self dataSize) < 0 ifTrue: [^self error: 'Invalid size for data']. ^self primAEDescToString: (String new: theSize).! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/21/1999 00:13'!asStringThenDispose | string | string _ self asString. self dispose. ^string! !!AEDesc methodsFor: 'converting' stamp: 'acg 9/26/1999 01:15'!to: aString | newAEDesc result | newAEDesc _ AEDesc new. result _ self primAECoerceDesc: (DescType of: aString) to: newAEDesc. result isZero ifFalse: [^result]. self dispose. self at: 1 put: (newAEDesc at: 1). self at: 2 put: (newAEDesc at: 2). ^0! !!AEDesc methodsFor: 'private' stamp: 'acg 9/24/1999 00:38'!createFromScpt: aCompiledApplescriptData (aCompiledApplescriptData class = CompiledApplescript) ifFalse: [^self error: 'textType Data Not From CompiledApplescriptData']. (self primAECreateDesc: (DescType of: 'scpt') from: aCompiledApplescriptData) isZero ifTrue: [^self]. self error: 'failed to create aeDesc'. ^nil! !!AEDesc methodsFor: 'private' stamp: 'acg 9/20/1999 14:39'!createFromText: aString (aString class = String) ifFalse: [^self error: 'TextType Data Not From String']. (self primAECreateDesc: (DescType of: 'TEXT') from: aString) isZero ifTrue: [^self]. self error: 'failed to create aeDesc'. ^nil! !!AEDesc methodsFor: 'private' stamp: 'acg 9/25/1999 22:54'!createNull (self primAECreateDesc: (DescType of: 'null') from: '') isZero ifTrue: [^self]. self error: 'failed to create aeDesc'. ^nil! !!AEDesc methodsFor: 'private' stamp: 'acg 9/23/1999 22:51'!primAECoerceDesc: typeCode to: result <primitive: 'primAECoerceDesc' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primAECoerceDesc:to:' withArguments: {typeCode. result}! !!AEDesc methodsFor: 'private' stamp: 'acg 9/20/1999 13:25'!primAECreateDesc: typeCode from: aString <primitive: 'primAECreateDesc' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primAECreateDesc:from:' withArguments: {typeCode. aString}! !!AEDesc methodsFor: 'private' stamp: 'acg 9/23/1999 21:13'!primAEDescToString: aString <primitive: 'primAEDescToString' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primAEDescToString:' withArguments: {aString}! !!AEDesc methodsFor: 'private' stamp: 'acg 9/20/1999 13:28'!primAEDisposeDesc <primitive: 'primAEDisposeDesc' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primAEDisposeDesc' withArguments: {}! !!AEDesc methodsFor: 'private' stamp: 'acg 9/23/1999 22:20'!primAEGetKeyPtr: keyDesc type: typeDesc actual: ignoreDesc to: aByteArray <primitive: 'primAEGetKeyPtr' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primAEGetKeyPtr:type:actual:to:' withArguments: {keyDesc. typeDesc. ignoreDesc. aByteArray}! !!AEDesc class methodsFor: 'as yet unclassified' stamp: 'acg 9/20/1999 22:17'!new ^super new: 2! !!AEDesc class methodsFor: 'as yet unclassified' stamp: 'acg 9/25/1999 22:53'!nullType ^self new createNull! !!AEDesc class methodsFor: 'as yet unclassified' stamp: 'acg 9/22/1999 08:05'!scptTypeOn: aCompiledApplescriptData ^(self new) createFromScpt: aCompiledApplescriptData ! !!AEDesc class methodsFor: 'as yet unclassified' stamp: 'acg 9/20/1999 13:30'!textTypeOn: aString ^(self new) createFromText: aString ! !!AEDesc class methodsFor: 'private' stamp: 'acg 9/12/1999 20:49'!primSizeAEDesc <primitive: 'primSizeAEDesc' module: 'OSAPlugin'> ^-1! !I am a parser for AIFF (audio interchange file format) files. I can read uncompressed 8-bit and 16-bit mono, stereo, or multichannel AIFF files. I read the marker information used by the TransferStation utility to mark the loop points in sounds extracted from commercial sampled-sound CD-ROMs.!!AIFFFileReader methodsFor: 'reading' stamp: 'jm 8/2/1998 16:27'!readFromFile: fileName "Read the AIFF file of the given name." "AIFFFileReader new readFromFile: 'test.aiff'" self readFromFile: fileName mergeIfStereo: false skipDataChunk: false.! !!AIFFFileReader methodsFor: 'reading' stamp: 'jm 3/24/1999 10:39'!readFromFile: fileName mergeIfStereo: mergeFlag skipDataChunk: skipDataFlag "Read the AIFF file of the given name. If mergeFlag is true and the file contains stereo data, then the left and right channels will be mixed together as the samples are read in. If skipDataFlag is true, then the data chunk to be skipped; this allows the other chunks of a file to be processed in order to extract format information quickly without reading the data." "AIFFFileReader new readFromFile: 'test.aiff' mergeIfStereo: false skipDataChunk: true" | f | mergeIfStereo _ mergeFlag. skipDataChunk _ skipDataFlag. f _ (FileStream readOnlyFileNamed: fileName) binary. isLooped _ false. gain _ 1.0. self readFrom: f. f close.! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 21:25'!bitsPerSample ^ bitsPerSample! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 21:24'!channelCount ^ channelCount! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 21:25'!channelData ^ channelData! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 21:24'!frameCount ^ frameCount! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 21:25'!gain ^ gain! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 7/12/1998 01:40'!isLooped ^ isLooped! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 20:02'!isStereo ^ channelData size = 2! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 7/12/1998 18:26'!leftSamples ^ channelData at: 1! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 7/12/1998 18:30'!loopEnd ^ markers last last! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 7/12/1998 18:30'!loopLength ^ markers last last - markers first last! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 21:25'!markers ^ markers! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 7/12/1998 01:48'!pitch ^ pitch! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 8/2/1998 19:34'!rightSamples ^ channelData at: 2! !!AIFFFileReader methodsFor: 'accessing' stamp: 'jm 7/12/1998 18:25'!samplingRate ^ samplingRate! !!AIFFFileReader methodsFor: 'other' stamp: 'jm 8/17/1998 20:36'!edit | ed | ed _ WaveEditor new. ed data: channelData first. ed loopEnd: markers last last. ed loopLength: (markers last last - markers first last) + 1. ed openInWorld.! !!AIFFFileReader methodsFor: 'other' stamp: 'jm 7/12/1998 01:44'!pitchForKey: midiKey "Convert my MIDI key number to a pitch and return it." | indexInOctave octave p | indexInOctave _ (midiKey \\ 12) + 1. octave _ (midiKey // 12) + 1. "Table generator: (0 to: 11) collect: [:i | 16.3516 * (2.0 raisedTo: i asFloat / 12.0)]" p _ #(16.3516 17.32391 18.35405 19.44544 20.60173 21.82677 23.12466 24.49972 25.95655 27.50000 29.13524 30.86771) at: indexInOctave. ^ p * (#(0.5 1.0 2.0 4.0 8.0 16.0 32.0 64.0 128.0 256.0 512.0) at: octave)! !!AIFFFileReader methodsFor: 'other' stamp: 'jm 1/14/1999 10:11'!sound "Answer the sound represented by this AIFFFileReader. This method should be called only after readFrom: has been done." | snd rightSnd | snd _ SampledSound samples: (channelData at: 1) samplingRate: samplingRate. self isStereo ifTrue: [ rightSnd _ SampledSound samples: (channelData at: 2) samplingRate: samplingRate. snd _ MixedSound new add: snd pan: 0; add: rightSnd pan: 1.0]. ^ snd! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 6/29/1998 07:33'!readChunk: chunkType size: chunkSize "Read a AIFF chunk of the given type. Skip unrecognized chunks. Leave the input stream positioned chunkSize bytes past its position when this method is called." chunkType = 'COMM' ifTrue: [^ self readCommonChunk: chunkSize]. chunkType = 'SSND' ifTrue: [^ self readSamplesChunk: chunkSize]. chunkType = 'INST' ifTrue: [^ self readInstrumentChunk: chunkSize]. chunkType = 'MARK' ifTrue: [^ self readMarkerChunk: chunkSize]. in skip: chunkSize. "skip unknown chunks"! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 7/12/1998 18:24'!readCommonChunk: chunkSize "Read a COMM chunk. All AIFF files have exactly one chunk of this type." | compressionType | channelCount _ in nextNumber: 2. frameCount _ in nextNumber: 4. bitsPerSample _ in nextNumber: 2. samplingRate _ self readExtendedFloat. chunkSize > 18 ifTrue: [ fileType = 'AIFF' ifTrue: [self error: 'unexpectedly long COMM chunk size for AIFF file']. compressionType _ (in next: 4) asString. compressionType = 'NONE' ifFalse: [self error: 'cannot read compressed AIFF files']. in skip: (chunkSize - 22)]. "skip the reminder of AIFF-C style chunk"! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 6/29/1998 11:43'!readExtendedFloat "Read and answer an Apple extended-precision 80-bit floating point number from the input stream." "Details: I could not find the specification for this format, so constants were determined empirically based on assumption of 1-bit sign, 15-bit exponent, 64-bit mantissa. This format does not seem to have an implicit one before the mantissa as some float formats do." | signAndExp mantissa sign exp | signAndExp _ in nextNumber: 2. mantissa _ in nextNumber: 8. "scaled by (2 raisedTo: -64) below" (signAndExp bitAnd: 16r8000) = 0 ifTrue: [sign _ 1.0] ifFalse: [sign _ -1.0]. exp _ (signAndExp bitAnd: 16r7FFF) - 16r4000 + 2. "not sure why +2 is needed..." ^ (sign * mantissa asFloat * (2.0 raisedTo: exp - 64)) roundTo: 0.00000001! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/2/1998 19:58'!readFrom: aBinaryStream "Read AIFF data from the given binary stream." "Details: An AIFF file consists of a header (FORM chunk) followed by a sequence of tagged data chunks. Each chunk starts with a header consisting of a four-byte tag (a string) and a four byte size. These eight bytes of chunk header are not included in the chunk size. For each chunk, the readChunk:size: method consumes chunkSize bytes of the input stream, parsing recognized chunks or skipping unrecognized ones. If chunkSize is odd, it will be followed by a padding byte. Chunks may occur in any order." | sz end chunkType chunkSize p | in _ aBinaryStream. "read FORM chunk" (in next: 4) asString = 'FORM' ifFalse: [^ self error: 'not an AIFF file']. sz _ in nextNumber: 4. end _ in position + sz. fileType _ (in next: 4) asString. [in atEnd not and: [in position < end]] whileTrue: [ chunkType _ (in next: 4) asString. chunkSize _ in nextNumber: 4. p _ in position. self readChunk: chunkType size: chunkSize. (in position = (p + chunkSize)) ifFalse: [self error: 'chunk size mismatch; bad AIFF file?']. chunkSize odd ifTrue: [in skip: 1]]. "skip padding byte"! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/5/1998 17:31'!readInstrumentChunk: chunkSize | midiKey detune lowNote highNote lowVelocity highVelocity sustainMode sustainStartID sustainEndID releaseMode releaseStartID releaseEndID | midiKey _ in next. detune _ in next. lowNote _ in next. highNote _ in next. lowVelocity _ in next. highVelocity _ in next. gain _ in nextNumber: 2. sustainMode _ in nextNumber: 2. sustainStartID _ in nextNumber: 2. sustainEndID _ in nextNumber: 2. releaseMode _ in nextNumber: 2. releaseStartID _ in nextNumber: 2. releaseEndID _ in nextNumber: 2. isLooped _ sustainMode = 1. (isLooped and: [markers notNil]) ifTrue: [ ((markers first last > frameCount) or: [markers last last > frameCount]) ifTrue: [ "bad loop data; some sample CD files claim to be looped but aren't" isLooped _ false]]. pitch _ self pitchForKey: midiKey.! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/2/1998 21:22'!readMarkerChunk: chunkSize | markerCount id position labelBytes label | markerCount _ in nextNumber: 2. markers _ Array new: markerCount. 1 to: markerCount do: [:i | id _ in nextNumber: 2. position _ in nextNumber: 4. labelBytes _ in next. label _ (in next: labelBytes) asString. labelBytes even ifTrue: [in skip: 1]. markers at: i put: (Array with: id with: label with: position)].! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/2/1998 18:58'!readMergedStereoChannelDataFrom: s "Read stereophonic channel data from the given stream, mixing the two channels to create a single monophonic channel. Each frame contains two samples." | buf w1 w2 | buf _ channelData at: 1. bitsPerSample = 8 ifTrue: [ 1 to: frameCount do: [:i | w1 _ s next. w1 > 127 ifTrue: [w1 _ w1 - 256]. w2 _ s next. w2 > 127 ifTrue: [w2 _ w2 - 256]. buf at: i put: ((w1 + w2) bitShift: 7)]] ifFalse: [ 1 to: frameCount do: [:i | w1 _ (s next bitShift: 8) + s next. w1 > 32767 ifTrue: [w1 _ w1 - 65536]. w2 _ (s next bitShift: 8) + s next. w2 > 32767 ifTrue: [w2 _ w2 - 65536]. buf at: i put: ((w1 + w2) bitShift: -1)]].! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/2/1998 18:53'!readMonoChannelDataFrom: s "Read monophonic channel data from the given stream. Each frame contains a single sample." | buf w | buf _ channelData at: 1. "the only buffer" bitsPerSample = 8 ifTrue: [ 1 to: frameCount do: [:i | w _ s next. w > 127 ifTrue: [w _ w - 256]. buf at: i put: (w bitShift: 8)]] ifFalse: [ 1 to: frameCount do: [:i | w _ (s next bitShift: 8) + s next. w > 32767 ifTrue: [w _ w - 65536]. buf at: i put: w]].! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/2/1998 18:55'!readMultiChannelDataFrom: s "Read multi-channel data from the given stream. Each frame contains channelCount samples." | w | bitsPerSample = 8 ifTrue: [ 1 to: frameCount do: [:i | 1 to: channelCount do: [:ch | w _ s next. w > 127 ifTrue: [w _ w - 256]. (channelData at: ch) at: i put: (w bitShift: 8)]]] ifFalse: [ 1 to: frameCount do: [:i | 1 to: channelCount do: [:ch | w _ (s next bitShift: 8) + s next. w > 32767 ifTrue: [w _ w - 65536]. (channelData at: ch) at: i put: w]]].! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/3/1998 14:55'!readSamplesChunk: chunkSize "Read a SSND chunk. All AIFF files with a non-zero frameCount contain exactly one chunk of this type." | offset blockSize bytesOfSamples s | skipDataChunk ifTrue: [in skip: chunkSize. ^ self]. offset _ in nextNumber: 4. blockSize _ in nextNumber: 4. ((offset ~= 0) or: [blockSize ~= 0]) ifTrue: [^ self error: 'this AIFF reader cannot handle blocked sample chunks']. bytesOfSamples _ chunkSize - 8. bytesOfSamples = (channelCount * frameCount * (bitsPerSample // 8)) ifFalse: [self error: 'actual sample count does not match COMM chunk']. (mergeIfStereo and: [channelCount = 2]) ifTrue: [ channelData _ Array with: (SoundBuffer newMonoSampleCount: frameCount)] ifFalse: [ channelData _ (1 to: channelCount) collect: [:i | SoundBuffer newMonoSampleCount: frameCount]]. (bytesOfSamples < (Smalltalk garbageCollectMost - 300000)) ifTrue: [s _ ReadStream on: (in next: bytesOfSamples)] "bulk-read, then process" ifFalse: [s _ in]. "not enough space to buffer; read directly from file" "mono and stereo are special-cased for better performance" channelCount = 1 ifTrue: [^ self readMonoChannelDataFrom: s]. channelCount = 2 ifTrue: [ mergeIfStereo ifTrue: [channelCount _ 1. ^ self readMergedStereoChannelDataFrom: s] ifFalse: [^ self readStereoChannelDataFrom: s]]. self readMultiChannelDataFrom: s.! !!AIFFFileReader methodsFor: 'private' stamp: 'jm 8/2/1998 18:56'!readStereoChannelDataFrom: s "Read stereophonic channel data from the given stream. Each frame contains two samples." | left right w | left _ channelData at: 1. right _ channelData at: 2. bitsPerSample = 8 ifTrue: [ 1 to: frameCount do: [:i | w _ s next. w > 127 ifTrue: [w _ w - 256]. left at: i put: (w bitShift: 8). w _ s next. w > 127 ifTrue: [w _ w - 256]. right at: i put: (w bitShift: 8)]] ifFalse: [ 1 to: frameCount do: [:i | w _ (s next bitShift: 8) + s next. w > 32767 ifTrue: [w _ w - 65536]. left at: i put: w. w _ (s next bitShift: 8) + s next. w > 32767 ifTrue: [w _ w - 65536]. right at: i put: w]].! !An AbsoluteAnimation is any animation where the final state of the animation is always the same. Every time this animation runs we store the initial state, so that when the animation is reversed and run we can determine what that end point should be.!!AbsoluteAnimation methodsFor: 'management' stamp: 'jsp 2/16/1999 16:36'!prologue: currentTime "Extends the AbstractAnimation prologue by saving the start state of the animation." undoable ifTrue: [ (myWonderland getUndoStack) push: (UndoAnimation new: (self makeUndoVersion)). ]. (direction = Forward) ifTrue: [ startState _ getStartStateFunction value. lastStartState _ startState. endState _ getEndStateFunction value. ] ifFalse: [ startState _ getStartStateFunction value. endState _ lastStartState. ]. super prologue: currentTime.! !!AbsoluteAnimation methodsFor: 'initialization' stamp: 'jsp 3/9/1999 15:49'!object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland "This method initializes the Animation with all the information that it needs to run." lastStartState _ startFunc value. super object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland.! !!AbsoluteAnimation methodsFor: 'copying' stamp: 'jsp 3/9/1999 15:49'!copy "Creates a copy of the animation" | anim | anim _ AbsoluteAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction style: styleFunction duration: duration undoable: undoable inWonderland: myWonderland. (direction = Forward) ifFalse: [ anim reverseDirection ]. ^ anim.! !!AbsoluteAnimation methodsFor: 'copying' stamp: 'jsp 3/9/1999 15:49'!makeUndoVersion "Creates the undo version of an animation" | anim | anim _ AbsoluteAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction style: styleFunction duration: 0.5 undoable: false inWonderland: myWonderland. anim stop. (direction = Forward) ifTrue: [ anim reverseDirection ]. ^ anim.! !!AbsoluteAnimation methodsFor: 'copying' stamp: 'jsp 4/9/1999 14:22'!reversed "Creates a reversed version of an animation" | anim | anim _ AbsoluteAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction style: styleFunction duration: duration undoable: true inWonderland: myWonderland. anim stop. (direction = Forward) ifTrue: [ anim reverseDirection ]. ^ anim.! !This class implements the basic functionality of Animations for Wonderlands. All animations pass through 4 specific stages:Waiting - this is the state animations are in when they are just started, before they run their prologue (perform any tasks they need to do before the animation actually starts)Running - this is the state animations are in when they are actually runningStopped - this is the state animations are in after they stop running but before they execute their prologueFinished - this is the state animations are in after they finish their epilogue (perform any tasks they need to do after the animation completes).!!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 3/9/1999 15:45'!getAnimatedObject "Return the object that this animation affects" ^ animatedObject.! !!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 2/26/1999 12:41'!getLoopCount "Returns the animation's current loop count" ^ loopCount.! !!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 2/4/1999 10:22'!getState "Returns the current state of the animation." ^ state.! !!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 2/3/1999 14:23'!isDone "Returns true if the animation is running" ^ (state = Stopped).! !!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 2/26/1999 12:01'!isLooping "Returns true if the animation is looping" ^ ( loopCount > 1) or: [ loopCount = Infinity ].! !!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 2/26/1999 12:42'!setLoopCount: count "Sets the animation's current loop count" loopCount _ count.! !!AbstractAnimation methodsFor: 'accessing' stamp: 'jsp 2/26/1999 12:23'!setUndoable: aBoolean "Sets the animation's undoable property" undoable _ aBoolean.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 3/3/1999 12:38'!copy self subclassResponsibility.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 3/3/1999 12:06'!epilogue: currentTime "This method does any work that needs to be done after an interation of the animation finishes." (loopCount = Infinity) ifTrue: [state _ Waiting] ifFalse: [ loopCount _ loopCount - 1. (loopCount > 0) ifTrue: [ state _ Waiting ] ifFalse: [state _ Stopped. loopCount _ 1 ]. ].! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 14:47'!getDuration "This method returns the duration of the animation." ^ duration.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 3/24/1999 15:48'!loop "This method causes an animation to loop forever." loopCount _ Infinity. (state = Stopped) ifTrue: [ state _ Waiting. myScheduler addAnimation: self. ].! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 15:10'!loop: numberOfTimes "This method causes an animation to loop for the specified number of times." loopCount _ numberOfTimes. (state = Stopped) ifTrue: [ state _ Waiting. myScheduler addAnimation: self. ].! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 3/3/1999 12:37'!looped "This method creates a copy of an animation and loops it forever." | anim | anim _ self copy. anim setLoopCount: Infinity. ^ anim.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 3/3/1999 12:36'!looped: numberOfTimes "This method creates a copy of an animation and loops it for the specified number of times." | anim | anim _ self copy. anim setLoopCount: numberOfTimes. ^ anim.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 14:43'!pause "This method pauses an active Animation." (state = Running) ifTrue: [ state _ Paused. pausedInterval _ (myScheduler getTime) - startTime.].! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 14:56'!prologue: currentTime "This method does any work that needs to be done before the animation starts, including possibly adding the current state to the undo stack." "Undo stack stuff here" undoable ifTrue: []. startTime _ currentTime. endTime _ startTime + duration. state _ Running.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/26/1999 15:21'!resume "This method resumes a paused animation" (state = Paused) ifTrue: [ state _ Running. startTime _ (myScheduler getTime) - pausedInterval. endTime _ startTime + duration. ] ifFalse: [(state = Stopped) ifTrue: [ state _ Waiting. myScheduler addAnimation: self. ]. ]! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 15:00'!start "This method starts an existing animation" state _ Waiting. loopCount _ 1. myScheduler addAnimation: self.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 14:25'!stop "This method changes the state of an animation to stopped. If it is currently active, the Scheduler will remove it from the list of active animations." state _ Stopped.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 14:50'!stopLooping "This method causes the animation to stop looping; the current interation of the animation completes before the animation stops." loopCount _ 1.! !!AbstractAnimation methodsFor: 'management' stamp: 'jsp 2/3/1999 14:53'!update: currentTime "Updates the animation using the current Wonderland time" (state = Waiting) ifTrue: [self prologue: currentTime]. (state = Running) ifTrue: []. (state = Finished) ifTrue: [self epilogue: currentTime].! !!AbstractAnimation methodsFor: 'reversing' stamp: 'jsp 2/15/1999 10:28'!reverseDirection "Changes the direction an animation runs in (forward or in reverse)" (direction = Forward) ifTrue: [ direction _ Reverse ] ifFalse: [ direction _ Forward ].! !!AbstractAnimation methodsFor: 'private' stamp: 'jsp 2/26/1999 14:21'!scaleDuration: scaleAmount "Scales the animation's duration by the specified amount" duration _ duration * scaleAmount.! !!AbstractAnimation methodsFor: 'private' stamp: 'jsp 2/26/1999 14:17'!setDirection: aDirection "Sets the animation's direction variable" direction _ aDirection.! !!AbstractAnimation class methodsFor: 'class initialization' stamp: 'jsp 3/24/1999 11:01'!initialize "Initialize the class variables" Waiting _ 1. Running _ 2. Paused _ 3. Finished _ 4. Stopped _ 5. Forward _ 0. Reverse _ 1. Infinity _ -1.! !AbstractFont defines the generic interface that all fonts need to implement.!!AbstractFont methodsFor: 'accessing' stamp: 'ar 5/19/2000 14:56'!characterToGlyphMap "Return the character to glyph mapping table. If the table is not provided the character scanner will query the font directly for the width of each individual character." ^nil! !!AbstractFont methodsFor: 'accessing' stamp: 'ar 5/19/2000 14:57'!xTable "Return the xTable for the font. The xTable defines the left x-value for each individual glyph in the receiver. If such a table is not provided, the character scanner will ask the font directly for the appropriate width of each individual character." ^nil! !!AbstractFont methodsFor: 'measuring' stamp: 'ar 5/19/2000 15:00'!composeWord: aTextLineInterval in: sourceString beginningAt: xInteger "Non-primitive composition of a word--add up widths of characters, add sum to beginning x and answer the resulting x. Similar to performance of scanning primitive, but without stop conditions." | character resultX | resultX _ xInteger. aTextLineInterval do: [:i | character _ sourceString at: i. resultX _ resultX + (self widthOf: character)]. ^resultX! !!AbstractFont methodsFor: 'measuring' stamp: 'ar 5/19/2000 14:58'!widthOf: aCharacter "Return the width of the given character" ^self subclassResponsibility! !!AbstractFont methodsFor: 'measuring' stamp: 'ar 5/19/2000 15:00'!widthOfString: aString ^ self composeWord: (1 to: aString size) in: aString beginningAt: 0" TextStyle default defaultFont widthOfString: 'zort' 21"! !!AbstractFont methodsFor: 'displaying' stamp: 'ar 5/19/2000 14:59'!displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta "Draw the given string from startIndex to stopIndex at aPoint on the (already prepared) display context." ^self subclassResponsibility! !!AbstractFont methodsFor: 'displaying' stamp: 'ar 5/19/2000 14:59'!installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor "Install the receiver on the given DisplayContext (either BitBlt or Canvas) for further drawing operations." ^self subclassResponsibility! !Contributed by Bob Arning as part of the ObjectExplorer package.!!AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 6/21/1999 15:22'!genericMenu: aMenu aMenu add: 'no menu yet' target: self selector: #yourself. ^aMenu! !!AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:44'!getCurrentSelection ^currentSelection! !!AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:46'!noteNewSelection: x currentSelection _ x. self changed: #getCurrentSelection. currentSelection ifNil: [^self]. currentSelection sendSettingMessageTo: self.! !!AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:53'!perform: selector orSendTo: otherTarget "Selector was just chosen from a menu by a user. If can respond, thenperform it on myself. If not, send it to otherTarget, presumably theeditPane from which the menu was invoked." (self respondsTo: selector) ifTrue: [^ self perform: selector] ifFalse: [^ otherTarget perform: selector]! !!AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:47'!update: aSymbol aSymbol == #hierarchicalList ifTrue: [ ^self changed: #getList ]. super update: aSymbol! !!AbstractScoreEvent methodsFor: 'accessing' stamp: 'di 6/17/1999 14:28'!adjustTimeBy: delta time _ time + delta! !!AbstractScoreEvent methodsFor: 'accessing' stamp: 'jm 8/27/1998 16:38'!endTime "Subclasses should override to return the ending time if the event has some duration." ^ time! !!AbstractScoreEvent methodsFor: 'classification' stamp: 'jm 9/10/1998 09:43'!isControlChange ^ false! !!AbstractScoreEvent methodsFor: 'classification' stamp: 'jm 9/10/1998 09:43'!isPitchBend ^ false! !!AbstractScoreEvent methodsFor: 'classification' stamp: 'jm 9/10/1998 09:43'!isProgramChange ^ false! !!AbstractScoreEvent methodsFor: 'midi' stamp: 'jm 9/10/1998 18:31'!outputOnMidiPort: aMidiPort "Output this event to the given MIDI port. This default implementation does nothing."! !!AbstractSound methodsFor: 'initialization' stamp: 'jm 3/24/1999 12:03'!loudness: aNumber "Initialize my volume envelopes and initial volume. Subclasses overriding this method should include a resend to super." | vol | vol _ (aNumber asFloat max: 0.0) min: 1.0. envelopes do: [:e | (e isKindOf: VolumeEnvelope) ifTrue: [e scale: vol]]. self initialVolume: vol.! !!AbstractSound methodsFor: 'initialization' stamp: 'jm 7/6/1998 17:04'!nameOrNumberToPitch: aStringOrNumber "Answer the pitch in cycles/second for the given pitch specification. The specification can be either a numeric pitch or pitch name such as 'c4'." aStringOrNumber isNumber ifTrue: [^ aStringOrNumber asFloat] ifFalse: [^ AbstractSound pitchForName: aStringOrNumber]! !!AbstractSound methodsFor: 'initialization' stamp: 'jm 8/19/1998 08:45'!setPitch: pitchNameOrNumber dur: d loudness: l "Initialize my envelopes for the given parameters. Subclasses overriding this method should include a resend to super." | p | p _ self nameOrNumberToPitch: pitchNameOrNumber. envelopes do: [:e | e volume: l. e centerPitch: p]. self initialVolume: l. self duration: d.! !!AbstractSound methodsFor: 'initialization' stamp: 'jm 8/3/1998 17:11'!soundForMidiKey: midiKey dur: d loudness: l "Answer an initialized sound object (a copy of the receiver) that generates a note for the given MIDI key (in the range 0..127), duration (in seconds), and loudness (in the range 0.0 to 1.0)." ^ self copy setPitch: (AbstractSound pitchForMIDIKey: midiKey) dur: d loudness: l! !!AbstractSound methodsFor: 'initialization' stamp: 'jm 8/3/1998 16:58'!soundForPitch: pitchNameOrNumber dur: d loudness: l "Answer an initialized sound object (a copy of the receiver) that generates a note of the given pitch, duration, and loudness. Pitch may be a numeric pitch or a string pitch name such as 'c4'. Duration is in seconds and loudness is in the range 0.0 to 1.0." ^ self copy setPitch: pitchNameOrNumber dur: d loudness: l! !!AbstractSound methodsFor: 'envelopes' stamp: 'jm 8/18/1998 09:57'!removeAllEnvelopes "Remove all envelopes from my envelopes list." envelopes _ #().! !!AbstractSound methodsFor: 'volume' stamp: 'jm 8/13/1998 16:37'!loudness "Answer the current volume setting for this sound." ^ scaledVol asFloat / ScaleFactor asFloat! !!AbstractSound methodsFor: 'volume' stamp: 'jm 8/13/1998 16:28'!volumeEnvelopeScaledTo: scalePoint "Return a collection of values representing my volume envelope scaled by the given point. The scale point's x component is pixels/second and its y component is the number of pixels for full volume." self error: 'not yet implemented'.! !!AbstractSound methodsFor: 'playing' stamp: 'ar 12/5/1998 22:20'!isPlaying "Return true if the receiver is currently playing" ^ SoundPlayer isPlaying: self! !!AbstractSound methodsFor: 'playing' stamp: 'di 5/30/1999 12:46'!millisecondsSinceStart ^ mSecsSinceStart! !!AbstractSound methodsFor: 'playing' stamp: 'jm 8/13/1998 15:09'!playAndWaitUntilDone "Play this sound to the sound ouput port and wait until it has finished playing before returning." SoundPlayer playSound: self. [self samplesRemaining > 0] whileTrue. (Delay forMilliseconds: 2 * SoundPlayer bufferMSecs) wait. "ensure last buffer has been output"! !!AbstractSound methodsFor: 'playing' stamp: 'jm 8/18/1998 10:52'!playChromaticRunFrom: startPitch to: endPitch "Play a fast chromatic run between the given pitches. Useful for auditioning a sound." (AbstractSound chromaticRunFrom: startPitch to: endPitch on: self) play.! !!AbstractSound methodsFor: 'playing' stamp: 'jm 8/13/1998 16:17'!playSampleCount: n into: aSoundBuffer startingAt: startIndex "Mix the next n samples of this sound into the given buffer starting at the given index. Update the receiver's control parameters periodically." | fullVol samplesBetweenControlUpdates pastEnd i remainingSamples count | fullVol _ AbstractSound scaleFactor. samplesBetweenControlUpdates _ self samplingRate // self controlRate. pastEnd _ startIndex + n. "index just after the last sample" i _ startIndex. [i < pastEnd] whileTrue: [ remainingSamples _ self samplesRemaining. remainingSamples <= 0 ifTrue: [^ self]. count _ pastEnd - i. samplesUntilNextControl < count ifTrue: [count _ samplesUntilNextControl]. remainingSamples < count ifTrue: [count _ remainingSamples]. self mixSampleCount: count into: aSoundBuffer startingAt: i leftVol: fullVol rightVol: fullVol. samplesUntilNextControl _ samplesUntilNextControl - count. samplesUntilNextControl <= 0 ifTrue: [ self doControl. samplesUntilNextControl _ samplesBetweenControlUpdates]. i _ i + count].! !!AbstractSound methodsFor: 'playing' stamp: 'jm 7/5/1998 17:53'!playSilently "Compute the samples of this sound without outputting them. Used for performance analysis." | bufSize buf | self reset. bufSize _ self samplingRate // 10. buf _ SoundBuffer newStereoSampleCount: bufSize. [self samplesRemaining > 0] whileTrue: [ buf primFill: 0. self playSampleCount: bufSize into: buf startingAt: 1].! !!AbstractSound methodsFor: 'playing' stamp: 'jm 8/19/1998 08:30'!viewSamples | stereoBuf | stereoBuf _ self computeSamplesForSeconds: self duration. WaveEditor openOn: stereoBuf extractLeftChannel.! !!AbstractSound methodsFor: 'sound generation' stamp: 'jm 8/17/1998 13:34'!doControl "Update the control parameters of this sound using its envelopes, if any." "Note: This is only called at a small fraction of the sampling rate." | pitchModOrRatioChange | envelopes size > 0 ifTrue: [ pitchModOrRatioChange _ false. 1 to: envelopes size do: [:i | ((envelopes at: i) updateTargetAt: mSecsSinceStart) ifTrue: [pitchModOrRatioChange _ true]]. pitchModOrRatioChange ifTrue: [self internalizeModulationAndRatio]]. mSecsSinceStart _ mSecsSinceStart + (1000 // self controlRate).! !!AbstractSound methodsFor: 'sound generation' stamp: 'jm 7/6/1998 06:40'!mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol "Mix the given number of samples with the samples already in the given buffer starting at the given index. Assume that the buffer size is at least (index + count) - 1. The leftVol and rightVol parameters determine the volume of the sound in each channel, where 0 is silence and ScaleFactor is full volume." self subclassResponsibility.! !!AbstractSound methodsFor: 'sound generation' stamp: 'jm 8/17/1998 13:45'!reset "Reset my internal state for a replay. Methods that override this method should do super reset." mSecsSinceStart _ 0. samplesUntilNextControl _ 0. envelopes size > 0 ifTrue: [ 1 to: envelopes size do: [:i | (envelopes at: i) reset]].! !!AbstractSound methodsFor: 'sound generation' stamp: 'jm 9/9/1998 21:56'!stopAfterMSecs: mSecs "Terminate this sound this note after the given number of milliseconds. This default implementation does nothing."! !!AbstractSound methodsFor: 'sound generation' stamp: 'jm 9/9/1998 21:54'!stopGracefully "End this note with a graceful decay. If the note has envelopes, determine the decay time from its envelopes." | decayInMs env | envelopes isEmpty ifTrue: [ self adjustVolumeTo: 0 overMSecs: 10. decayInMs _ 10] ifFalse: [ env _ envelopes first. decayInMs _ env attackTime + env decayTime]. self duration: (mSecsSinceStart + decayInMs) / 1000.0. self stopAfterMSecs: decayInMs.! !!AbstractSound methodsFor: 'composition' stamp: 'jm 2/2/1999 15:53'!asSound ^ self! !!AbstractSound methodsFor: 'copying' stamp: 'di 3/4/1999 21:29'!sounds "Allows simple sounds to behave as, eg, sequential sounds" ^ Array with: self! !!AbstractSound methodsFor: 'file i/o' stamp: 'jm 3/13/1999 11:47'!storeAIFFOnFileNamed: fileName | f | f _ (FileStream fileNamed: fileName) binary. self storeAIFFSamples: self samples samplingRate: self originalSamplingRate on: f. f close.! !!AbstractSound methodsFor: 'file i/o' stamp: 'jm 3/13/1999 11:48'!storeAIFFSamples: aSoundBuffer samplingRate: rate on: aBinaryStream | sampleCount s | sampleCount _ aSoundBuffer monoSampleCount. aBinaryStream nextPutAll: 'FORM' asByteArray. aBinaryStream nextInt32Put: (2 * sampleCount) + ((7 * 4) + 18). aBinaryStream nextPutAll: 'AIFF' asByteArray. aBinaryStream nextPutAll: 'COMM' asByteArray. aBinaryStream nextInt32Put: 18. aBinaryStream nextNumber: 2 put: 1. "channels" aBinaryStream nextInt32Put: sampleCount. aBinaryStream nextNumber: 2 put: 16. "bits/sample" self storeExtendedFloat: rate on: aBinaryStream. aBinaryStream nextPutAll: 'SSND' asByteArray. aBinaryStream nextInt32Put: (2 * sampleCount) + 8. aBinaryStream nextInt32Put: 0. aBinaryStream nextInt32Put: 0. 1 to: sampleCount do: [:i | s _ aSoundBuffer at: i. aBinaryStream nextPut: ((s bitShift: -8) bitAnd: 16rFF). aBinaryStream nextPut: (s bitAnd: 16rFF)].! !!AbstractSound methodsFor: 'file i/o' stamp: 'jm 3/13/1999 11:34'!storeExtendedFloat: aNumber on: aBinaryStream "Store an Apple extended-precision 80-bit floating point number on the given stream." "Details: I could not find the specification for this format, so constants were determined empirically based on assumption of 1-bit sign, 15-bit exponent, 64-bit mantissa. This format does not seem to have an implicit one before the mantissa as some float formats do." | n isNeg exp mantissa | n _ aNumber asFloat. isNeg _ false. n < 0.0 ifTrue: [ n _ 0.0 - n. isNeg _ true]. exp _ (n log: 2.0) ceiling. mantissa _ (n * (2 raisedTo: 64 - exp)) truncated. exp _ exp + 16r4000 - 2. "not sure why the -2 is needed..." isNeg ifTrue: [exp _ exp bitOr: 16r8000]. "set sign bit" aBinaryStream nextPut: ((exp bitShift: -8) bitAnd: 16rFF). aBinaryStream nextPut: (exp bitAnd: 16rFF). 8 to: 1 by: -1 do: [:i | aBinaryStream nextPut: (mantissa digitAt: i)].! !!AbstractSound methodsFor: 'conversion' stamp: 'mjg 12/3/1999 12:58'!asSampledSound ^SampledSound samples: (self computeSamplesForSeconds: self duration) samplingRate: (self samplingRate)*2.! !!AbstractSound class methodsFor: 'class initialization' stamp: 'jm 8/3/1998 16:13'!initialize "AbstractSound initialize" | bottomC | ScaleFactor _ 2 raisedTo: 15. FloatScaleFactor _ ScaleFactor asFloat. MaxScaledValue _ ((2 raisedTo: 31) // ScaleFactor) - 1. "magnitude of largest scaled value in 32-bits" "generate pitches for c-1 through c0" bottomC _ (440.0 / 32) * (2.0 raisedTo: -9.0 / 12.0). PitchesForBottomOctave _ (0 to: 12) collect: [:i | bottomC * (2.0 raisedTo: i asFloat / 12.0)]. TopOfBottomOctave _ PitchesForBottomOctave last.! !!AbstractSound class methodsFor: 'instance creation' stamp: 'jm 8/3/1998 17:00'!noteSequenceOn: aSound from: anArray "Build a note sequence (i.e., a SequentialSound) from the given array using the given sound as the instrument. Elements are either (pitch, duration, loudness) triples or (#rest duration) pairs. Pitches can be given as names or as numbers." | score pitch | score _ SequentialSound new. anArray do: [:el | el size = 3 ifTrue: [ pitch _ el at: 1. pitch isNumber ifFalse: [pitch _ self pitchForName: pitch]. score add: ( aSound soundForPitch: pitch dur: (el at: 2) loudness: (el at: 3) / 1000.0)] ifFalse: [ score add: (RestSound dur: (el at: 2))]]. ^ score! !!AbstractSound class methodsFor: 'utilities' stamp: 'jm 8/3/1998 16:16'!indexOfBottomOctavePitch: p "Answer the index of the first pitch in the bottom octave equal to or higher than the given pitch. Assume that the given pitch is below the top pitch of the bottom octave." 1 to: PitchesForBottomOctave size do: [:i | (PitchesForBottomOctave at: i) >= p ifTrue: [^ i]]. self error: 'implementation error: argument pitch should be below or within the bottom octave'.! !!AbstractSound class methodsFor: 'utilities' stamp: 'jm 8/3/1998 16:16'!midiKeyForPitch: pitchNameOrNumber "Answer the midiKey closest to the given pitch. Pitch may be a numeric pitch or a pitch name string such as 'c4'." "AbstractSound midiKeyForPitch: 440.0" | p octave i midiKey | pitchNameOrNumber isNumber ifTrue: [p _ pitchNameOrNumber asFloat] ifFalse: [p _ AbstractSound pitchForName: pitchNameOrNumber]. octave _ -1. [p >= TopOfBottomOctave] whileTrue: [ octave _ octave + 1. p _ p / 2.0]. i _ self indexOfBottomOctavePitch: p. (i > 1) ifTrue: [ (p - (PitchesForBottomOctave at: i - 1)) < ((PitchesForBottomOctave at: i) - p) ifTrue: [i _ i - 1]]. midiKey _ ((octave * 12) + 11 + i). midiKey > 127 ifTrue: [midiKey _ 127]. ^ midiKey! !!AbstractSound class methodsFor: 'utilities' stamp: 'jm 8/3/1998 16:43'!pitchForMIDIKey: midiKey "Answer the pitch for the given MIDI key." "(1 to: 127) collect: [:i | AbstractSound pitchForMIDIKey: i]" | indexInOctave octave | indexInOctave _ (midiKey \\ 12) + 1. octave _ (midiKey // 12) + 1. ^ (PitchesForBottomOctave at: indexInOctave) * (#(1.0 2.0 4.0 8.0 16.0 32.0 64.0 128.0 256.0 512.0 1024.0) at: octave)! !!AbstractSound class methodsFor: 'utilities' stamp: 'jm 7/6/1998 15:47'!pitchTable "AbstractSound pitchTable" | out note i | out _ WriteStream on: (String new: 1000). i _ 12. 0 to: 8 do: [:octave | #(c 'c#' d eb e f fs g 'g#' a bf b) do: [:noteName | note _ noteName, octave printString. out nextPutAll: note; tab. out nextPutAll: i printString; tab. out nextPutAll: (AbstractSound pitchForName: note) printString; cr. i _ i + 1]]. ^ out contents! !!AbstractSound class methodsFor: 'examples' stamp: 'jm 6/30/1998 18:40'!chromaticPitchesFrom: aPitch | halfStep pitch | halfStep _ 2.0 raisedTo: (1.0 / 12.0). pitch _ aPitch isNumber ifTrue: [aPitch] ifFalse: [self pitchForName: aPitch]. pitch _ pitch / halfStep. ^ (0 to: 14) collect: [:i | pitch _ pitch * halfStep]! !!AbstractSound class methodsFor: 'examples' stamp: 'jm 8/18/1998 11:32'!chromaticRunFrom: startPitch to: endPitch on: aSound "Answer a composite sound consisting of a rapid chromatic run between the given pitches on the given sound." "(AbstractSound chromaticRunFrom: 'c3' to: 'c#5' on: FMSound oboe1) play" | scale halfStep pEnd p | scale _ SequentialSound new. halfStep _ 2.0 raisedTo: (1.0 / 12.0). endPitch isNumber ifTrue: [pEnd _ endPitch asFloat] ifFalse: [pEnd _ AbstractSound pitchForName: endPitch]. startPitch isNumber ifTrue: [p _ startPitch asFloat] ifFalse: [p _ AbstractSound pitchForName: startPitch]. [p <= pEnd] whileTrue: [ scale add: (aSound soundForPitch: p dur: 0.2 loudness: 0.5). p _ p * halfStep]. ^ scale! !!AbstractSound class methodsFor: 'examples' stamp: 'jm 8/3/1998 17:00'!majorChordOn: aSound from: aPitch "FMSound majorChord play" | score majorScale leadingRest pan note | majorScale _ self majorPitchesFrom: aPitch. score _ MixedSound new. leadingRest _ pan _ 0. #(1 3 5 8) do: [:noteIndex | note _ aSound soundForPitch: (majorScale at: noteIndex) dur: 2.0 - leadingRest loudness: 0.3. score add: (RestSound dur: leadingRest), note pan: pan. leadingRest _ leadingRest + 0.2. pan _ pan + 0.3]. ^ score! !!AbstractSound class methodsFor: 'examples' stamp: 'jm 7/13/1998 13:09'!majorScaleOn: aSound from: aPitch "FMSound majorScale play" ^ self noteSequenceOn: aSound from: ((self majorPitchesFrom: aPitch) collect: [:pitch | Array with: pitch with: 0.5 with: 300])! !!AbstractSound class methodsFor: 'examples' stamp: 'jm 1/4/1999 09:26'!majorScaleOn: aSound from: aPitch octaves: octaveCount "(AbstractSound majorScaleOn: FMSound oboe1 from: #c2 octaves: 5) play" | startingPitch pitches chromatic | startingPitch _ aPitch isNumber ifTrue: [aPitch] ifFalse: [self pitchForName: aPitch]. pitches _ OrderedCollection new. 0 to: octaveCount - 1 do: [:i | chromatic _ self chromaticPitchesFrom: startingPitch * (2 raisedTo: i). #(1 3 5 6 8 10 12) do: [:j | pitches addLast: (chromatic at: j)]]. pitches addLast: startingPitch * (2 raisedTo: octaveCount). ^ self noteSequenceOn: aSound from: (pitches collect: [:pitch | Array with: pitch with: 0.5 with: 300])! !!AbstractSound class methodsFor: 'examples' stamp: 'di 4/13/1999 13:53'!testFMInteractively "Experiment with different settings of the FM modulation and multiplier settings interactively by moving the mouse. The top-left corner of the screen is 0 for both parameters. Stop when the mouse is pressed." "AbstractSound testFMInteractively" | s mousePt lastVal status mod ratio | SoundPlayer startPlayerProcessBufferSize: 1100 rate: 11025 stereo: false. s _ FMSound pitch: 440.0 dur: 200.0 loudness: 0.2. SoundPlayer playSound: s. lastVal _ nil. [Sensor anyButtonPressed] whileFalse: [ mousePt _ Sensor cursorPoint. mousePt ~= lastVal ifTrue: [ mod _ mousePt x asFloat / 20.0. ratio _ mousePt y asFloat / 20.0. s modulation: mod ratio: ratio. lastVal _ mousePt. status _'mod: ', mod printString, 'ratio: ', ratio printString. status displayOn: Display at: 10@10]]. SoundPlayer shutDown.! !!AbstractSound class methodsFor: 'sound library' stamp: 'jm 8/14/1998 13:27'!initSounds "AbstractSound initSounds" Sounds _ Dictionary new. (FMSound class organization listAtCategoryNamed: #instruments) do: [:sel | Sounds at: sel asString put: (FMSound perform: sel)].! !!AbstractSound class methodsFor: 'sound library' stamp: 'jm 8/14/1998 13:25'!soundNamed: soundName ^ Sounds at: soundName! !!AbstractSound class methodsFor: 'sound library' stamp: 'tk 6/24/1999 11:31'!soundNamed: soundName put: aSound Sounds at: soundName put: aSound. Smalltalk at: #ScorePlayerMorph ifPresent: [:playerClass | playerClass allSubInstancesDo: [:player | player updateInstrumentsFromLibrary]].! !!AbstractSound class methodsFor: 'sound library' stamp: 'jm 8/19/1998 14:11'!soundNames ^ Sounds keys asSortedCollection asArray! !!AbstractSound class methodsFor: 'sound library' stamp: 'jm 8/4/1998 18:26'!sounds ^ Sounds! !!AbstractSound class methodsFor: 'sound library' stamp: 'jm 1/14/1999 13:00'!updateFMSounds "AbstractSound updateFMSounds" Sounds keys do: [:k | ((Sounds at: k) isKindOf: FMSound) ifTrue: [ Sounds removeKey: k ifAbsent: []]]. (FMSound class organization listAtCategoryNamed: #instruments) do: [:sel | Sounds at: sel asString put: (FMSound perform: sel)].! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'sge 2/13/2000 05:20'!fileInSoundLibrary "Prompt the user for a file name and the file in the sound library with that name." "AbstractSound fileInSoundLibrary" | fileName | fileName _ FillInTheBlank request: 'Sound library file name?'. fileName isEmptyOrNil ifTrue: [^ self]. (fileName endsWith: '.sounds') ifFalse: [fileName _ fileName, '.sounds']. self fileInSoundLibraryNamed: fileName.! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'tk 6/24/1999 07:20'!fileInSoundLibraryNamed: fileName "File in the sound library with the given file name, and add its contents to the current sound library." | s newSounds | s _ FileStream oldFileNamed: fileName. newSounds _ s fileInObjectAndCode. s close. newSounds associationsDo: [:assoc | self storeFiledInSound: assoc value named: assoc key]. ScorePlayerMorph allSubInstances do: [:p | p updateInstrumentsFromLibrary]. Smalltalk garbageCollect.! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'jm 8/19/1998 12:42'!fileOutSoundLibrary "File out the current sound library." "AbstractSound fileOutSoundLibrary" self fileOutSoundLibrary: Sounds.! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'sge 2/13/2000 05:22'!fileOutSoundLibrary: aDictionary "File out the given dictionary, which is assumed to contain sound and instrument objects keyed by their names." "Note: This method is separated out so that one can file out edited sound libraries, as well as the system sound library. To make such a collection, you can inspect AbstractSound sounds and remove the items you don't want. Then do: 'AbstractSound fileOutSoundLibrary: self' from the Dictionary inspector." | fileName refStream | (aDictionary isKindOf: Dictionary) ifFalse: [self error: 'arg should be a dictionary of sounds']. fileName _ FillInTheBlank request: 'Sound library file name?'. fileName isEmptyOrNil ifTrue: [^ self]. refStream _ SmartRefStream fileNamed: fileName, '.sounds'. refStream nextPut: aDictionary. refStream close.! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'jm 9/12/1998 21:35'!storeFiledInSound: snd named: sndName "Store the given sound in the sound library. Use the given name if it isn't in use, otherwise ask the user what to do." | menu choice i | (Sounds includesKey: sndName) ifFalse: [ "no name clash" Sounds at: sndName put: snd. ^ self]. (Sounds at: sndName) == UnloadedSnd ifTrue: [ "re-loading a sound that was unloaded to save space" Sounds at: sndName put: snd. ^ self]. "the given sound name is already used" menu _ SelectionMenu selections: #('replace the existing sound' 'rename the new sound' 'skip it'). choice _ menu startUpWithCaption: '"', sndName, '" has the same name as an existing sound'. (choice beginsWith: 'replace') ifTrue: [ Sounds at: sndName put: snd. ^ self]. (choice beginsWith: 'rename') ifTrue: [ i _ 2. [Sounds includesKey: (sndName, ' v', i printString)] whileTrue: [i _ i + 1]. Sounds at: (sndName, ' v', i printString) put: snd].! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'jm 9/12/1998 22:18'!unloadSampledTimbres "This can be done to unload those bulky sampled timbres to shrink the image. The unloaded sounds are replaced by a well-known 'unloaded sound' object to enable the unloaded sounds to be detected when the process is reversed." "AbstractSound unloadSampledTimbres" Sounds keys copy do: [:soundName | (((Sounds at: soundName) isKindOf: SampledInstrument) or: [(Sounds at: soundName) isKindOf: LoopedSampledSound]) ifTrue: [ Sounds at: soundName put: self unloadedSound]]. self updateScorePlayers. Smalltalk garbageCollect.! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'jm 9/11/1998 16:47'!unloadSoundNamed: soundName (Sounds includesKey: soundName) ifTrue: [ Sounds at: soundName put: self unloadedSound]. self updateScorePlayers.! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'jm 9/12/1998 21:48'!unloadedSound "Answer a sound to be used as the place-holder for sounds that have been unloaded." UnloadedSnd ifNil: [UnloadedSnd _ UnloadedSound default copy]. ^ UnloadedSnd! !!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'tk 6/24/1999 07:20'!updateScorePlayers "Force all ScorePlayers to update their instrument list from the sound library. This may done after loading, unloading, or replacing a sound to make all ScorePlayers feel the change." ScorePlayer allSubInstances do: [:p | p pause]. SoundPlayer shutDown. ScorePlayerMorph allInstances do: [:p | p updateInstrumentsFromLibrary].! !!AbstractSound class methodsFor: 'primitive generation' stamp: 'jm 8/19/1998 14:22'!cCodeForSoundPrimitives "Return a string containing the C code for the sound primitives. This string is pasted into a file, compiled, and linked into the virtual machine. Note that the virtual machine's primitive table must also be edited to make new primitives available." "AbstractSound cCodeForSoundPrimitives" ^ CCodeGenerator new codeStringForPrimitives: #( (FMSound mixSampleCount:into:startingAt:leftVol:rightVol:) (PluckedSound mixSampleCount:into:startingAt:leftVol:rightVol:) (LoopedSampledSound mixSampleCount:into:startingAt:leftVol:rightVol:) (SampledSound mixSampleCount:into:startingAt:leftVol:rightVol:) (ReverbSound applyReverbTo:startingAt:count:) ).! !!AcceptableCleanTextMorph methodsFor: 'as yet unclassified' stamp: 'di 6/22/1998 21:38'!accept "Overridden to allow accept of clean text" | textToAccept ok | textToAccept _ textMorph asText. ok _ (setTextSelector == nil) or: [setTextSelector numArgs = 2 ifTrue: [model perform: setTextSelector with: textToAccept with: self] ifFalse: [model perform: setTextSelector with: textToAccept]]. ok ifTrue: [self setText: self getText. self hasUnacceptedEdits: false]! !!AcornFileDirectory methodsFor: 'file name utilities' stamp: 'ar 12/18/1999 00:47'!fullPathFor: path path isEmpty ifTrue:[^pathName]. ((path includes: $$ ) or:[path includes: $:]) ifTrue:[^path]. ^pathName, self slash, path! !!AcornFileDirectory class methodsFor: 'platform specific' stamp: 'TPR 5/12/1998 22:48'!isActiveDirectoryClass "Does this class claim to be that properly active subclass of FileDirectory for this platform? On Acorn, the test is whether systemAttribute 1001 = 'RiscOS' (on newer VMs) or if the primPathNameDelimiter is $. (on older ones), which is what we would like to use for a dirsep if only it would work out. See pathNameDelimiter for more woeful details - then just get on and enjoy Squeak" | attr | attr _ Smalltalk getSystemAttribute: 1001. attr isNil ifFalse:[^attr = 'RiscOS']. ^self primPathNameDelimiter = $.! !!AcornFileDirectory class methodsFor: 'platform specific' stamp: 'TPR 7/20/1999 17:52'!maxFileNameLength ^ 255! !!AcornFileDirectory class methodsFor: 'platform specific' stamp: 'TPR 5/10/1998 21:45'!pathNameDelimiter"Acorn RiscOS uses a dot as the directory separator and has no real concept of filename extensions. We tried to make code handle this, but there are just too many uses of dot as a filename extension - so fake it out by pretending to use a slash. The file prims do conversions instead.Sad, but pragmatic" ^ $/! !This class implements Actions for Wonderlands. An Action is some task that should be executed every frame either forever, until a specified amount of time has elapsed, or until a specified condition holds true.!!Action methodsFor: 'accessing' stamp: 'jsp 3/9/1999 16:08'!getAffectedObject "Returns the object affected by the action" ^ affectedObject.! !!Action methodsFor: 'accessing' stamp: 'jsp 2/1/1999 15:13'!isDone "Returns true if the Action is done executing either because it's lifetime has expired or because the specified condition is true" (lifetime > 0) ifTrue: [^ (lifetime < (myScheduler getTime))] ifFalse: [^ (stopCondition value)]. ! !!Action methodsFor: 'accessing' stamp: 'jsp 3/9/1999 16:22'!isPaused "Returns true if the action is paused" ^ paused.! !!Action methodsFor: 'accessing' stamp: 'jsp 3/9/1999 16:21'!pause "Pause the action" paused _ true.! !!Action methodsFor: 'accessing' stamp: 'jsp 3/9/1999 16:21'!resume "resume the action" paused _ false.! !!Action methodsFor: 'management' stamp: 'jsp 3/9/1999 16:20'!execute "Execute the Action's task" paused ifFalse: [ actionTask value ].! !!Action methodsFor: 'management' stamp: 'jsp 3/9/1999 16:08'!setAffectedObject: anObject "Sets the object affected by the action" affectedObject _ anObject.! !!Action methodsFor: 'management' stamp: 'jsp 2/1/1999 11:44'!setLifetime: howlong andCondition: condition "Sets how long the action should run, or the condition under which it should stop" lifetime _ howlong. stopCondition _ condition.! !!Action methodsFor: 'management' stamp: 'jsp 2/1/1999 16:20'!setScheduler: scheduler "Sets the scheduler the Action is active in" myScheduler _ scheduler.! !!Action methodsFor: 'management' stamp: 'jsp 3/9/1999 16:20'!setTask: task "Sets the task the Action should perform each frame" actionTask _ task. paused _ false.! !!Action methodsFor: 'management' stamp: 'jsp 3/30/1999 11:50'!stop "This method removes the Action from myScheduler's list of active actions" stopCondition _ [ true ]. myScheduler removeAction: self.! !!Action class methodsFor: 'initialize-release' stamp: 'jsp 3/9/1999 16:09'!do: task eachframefor: time toObject: anObject inScheduler: scheduler "Creates a new Action that performs the specified task each frame for (time) seconds" | newAction | newAction _ Action new. newAction setTask: task. newAction setLifetime: (time + (scheduler getTime)) andCondition: [false]. newAction setAffectedObject: anObject. newAction setScheduler: scheduler. scheduler addAction: newAction. ^ newAction.! !!Action class methodsFor: 'initialize-release' stamp: 'jsp 3/9/1999 16:09'!do: task eachframeuntil: condition toObject: anObject inScheduler: scheduler "Creates a new Action that performs the specified task each frame until the specified condition holds true" | newAction | newAction _ Action new. newAction setTask: task. newAction setLifetime: -1 andCondition: condition. newAction setAffectedObject: anObject. newAction setScheduler: scheduler. scheduler addAction: newAction. ^ newAction.! !!Action class methodsFor: 'initialize-release' stamp: 'jsp 3/9/1999 16:10'!do: task toObject: anObject inScheduler: scheduler "Creates a new Action that executes the specified task each frame" | newAction | newAction _ Action new. newAction setTask: task. newAction setLifetime: -1 andCondition: [false]. newAction setAffectedObject: anObject. newAction setScheduler: scheduler. scheduler addAction: newAction. ^ newAction.! !!ActiveSwikiAction methodsFor: 'as yet unclassified' stamp: 'mjg 9/1/199812:44'!browse: pageRef from: request "Just reply with a page in HTML format" | formattedPage liveText| liveText _ HTMLformatter evalEmbedded: (pageRef text) with: request unlessContains: (self dangerSet). formattedPage _ pageRef copy. "Make a copy, then format the text." formattedPage formatted: (formatter swikify: liveText linkhandler: [:link | urlmap linkFor: link from: request peerName storingTo: OrderedCollection new page: formattedPage]). request reply: ((self formatterFor: 'page') format: formattedPage).! !!ActiveSwikiAction methodsFor: 'as yet unclassified' stamp: 'mjg 9/10/199815:33'!inputFrom: request "Take user's input and respond with a searchresult or store the edit" | coreRef page theText | coreRef _ request message size < 2 ifTrue: ['1'] ifFalse: [request message at: 2]. coreRef = 'searchresult' ifTrue: [ "If contains search string, do search" request reply: PWS crlf, (HTMLformatter evalEmbedded: (self fileContents:source, 'results.html') with: (urlmap searchFor: (request fieldsat: 'searchFor' ifAbsent: ['nothing']))). ^ #return]. (theText _ request fields at: 'text' ifAbsent: [nil]) ifNotNil: [ "It's a response from an edit, so store the page" page _ urlmap atID: coreRef. page user: request peerName. "Address is machine, user only iflogged in" page pageStatus = #new ifTrue: [page pageStatus: #standard]. page _ urlmap storeID: coreRef text: theText withSqueakLineEndings from: request peerName. ^ self]. "return self means do serve the edited pageafterwards" request fields keys do: [:aTag | (aTag beginsWith: 'text-') ifTrue: [ urlmap storeID: coreRef text: (request fields at: aTag)withSqueakLineEndings insertAt: (aTag copyFrom: 6 to: aTag size). "string" ^ self]]. "oops, a new kind!! -- but don't complain!! Could be for ActivePage!!"" Transcript show: 'Unknown data from client. '; show: request fieldsprintString; cr."! !!ActorState methodsFor: 'pen' stamp: 'di 9/3/1999 09:16'!choosePenColor: evt evt hand changeColorTarget: owningPlayer costume selector: #penColor: originalColor: owningPlayer penColor.! !!ActorState methodsFor: 'other' stamp: 'MPW 1/1/1901 21:53'!printOnStream: aStream aStream print: 'ActorState for '; print:owningPlayer externalName; print:' '. penDown ifNotNil: [aStream cr; print: 'penDown '; write:penDown]. penColor ifNotNil: [aStream cr; print: 'penColor '; write:penColor]. penSize ifNotNil: [aStream cr; print: 'penSize '; write:penSize]. instantiatedUserScriptsDictionary ifNotNil: [aStream cr; print: '+ '; write: instantiatedUserScriptsDictionary size; print:' user scripts'].! !!AdvancedB3DSceneMorph methodsFor: 'accessing' stamp: 'ti 3/24/2000 16:36'!rotationAngle ^rotationAngle! !!AdvancedB3DSceneMorph methodsFor: 'accessing' stamp: 'ti 3/24/2000 16:36'!rotationAngle: aNumber rotationAngle := aNumber! !!AdvancedB3DSceneMorph methodsFor: 'accessing' stamp: 'ti 3/27/2000 16:55'!scene: aScene super scene: aScene. self updateHeadlight. self changed! !!AdvancedB3DSceneMorph methodsFor: 'accessing' stamp: 'ti 3/24/2000 16:35'!stepTime ^stepTime! !!AdvancedB3DSceneMorph methodsFor: 'accessing' stamp: 'ti 3/24/2000 16:35'!stepTime: aNumber stepTime := aNumber! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:55'!addDolly: delta | camera new | camera := scene defaultCamera. new := camera position - (camera direction * delta). camera target = new ifFalse: [ camera position: new]. self updateHeadlight. self changed.! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:55'!addFovAngle: delta | camera new | camera := scene defaultCamera. new := camera fov + delta. 0 < new ifTrue: [ camera fov: new]. self updateHeadlight. self changed.! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:54'!panBy: aPoint | camera pt | pt := B3DVector3 x: aPoint x y: aPoint y negated z: 0.0. camera := scene defaultCamera. pt := pt * (camera direction length) / 200. pt := camera asMatrix4x4 inverseTransformation localPointToGlobal: pt. pt := pt - camera position. camera position: camera position + pt. camera target: camera target + pt. self updateHeadlight. self changed.! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:55'!rotateX: angle | camera matrix | camera := scene defaultCamera. matrix := B3DMatrix4x4 rotatedBy: angle around: ((camera position - camera target) cross: camera up) centeredAt: camera target. camera position: (matrix localPointToGlobal: camera position). camera up: (matrix localPointToGlobal: camera up). self updateHeadlight. self changed.! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:55'!rotateY: angle | camera matrix | camera := scene defaultCamera. matrix := B3DMatrix4x4 rotatedBy: angle around: camera up centeredAt: camera target. camera position: (matrix localPointToGlobal: camera position). self updateHeadlight. self changed.! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:54'!rotateZ: angle | camera matrix | camera := scene defaultCamera. matrix := B3DMatrix4x4 rotatedBy: angle around: (camera position - camera target) centeredAt: camera target. camera up: (matrix localPointToGlobal: camera up). self updateHeadlight. self changed.! !!AdvancedB3DSceneMorph methodsFor: 'camera actions' stamp: 'ti 3/27/2000 16:54'!updateHeadlight | headLight camera | camera := scene defaultCamera. (self scene lights isKindOf: Dictionary) ifTrue: [headLight := self scene lights at: '$HeadLight$' ifAbsent: []] ifFalse: [headLight := nil]. headLight ifNotNil: [ headLight position: camera position; target: camera target].! !!AdvancedB3DSceneMorph methodsFor: 'drawing' stamp: 'ti 3/24/2000 17:12'!renderOn: aRenderer aRenderer getVertexBuffer flags: (aRenderer getVertexBuffer flags bitOr: VBTwoSidedLighting). super renderOn: aRenderer! !!AdvancedB3DSceneMorph methodsFor: 'event handling' stamp: 'ti 3/24/2000 17:01'!handlesMouseDown: evt evt yellowButtonPressed ifTrue: [^false] ifFalse: [^true]! !!AdvancedB3DSceneMorph methodsFor: 'event handling' stamp: 'ti 3/24/2000 17:02'!mouseDown: evt oldPoint := evt cursorPoint. super mouseDown: evt.! !!AdvancedB3DSceneMorph methodsFor: 'event handling' stamp: 'ti 3/24/2000 17:02'!mouseMove: evt oldPoint ifNil: [^super mouseMove: evt]. ((evt redButtonPressed) and: [evt shiftPressed]) ifTrue: [ self panBy: oldPoint - evt cursorPoint. oldPoint := evt cursorPoint.]! !!AdvancedB3DSceneMorph methodsFor: 'initialization' stamp: 'ti 3/27/2000 10:51'!createDefaultScene | camera headLight | super createDefaultScene. camera _ B3DCamera new. camera position: 0@0@-6. camera target: 0@0@0. camera fov: 15.0. scene defaultCamera: camera. headLight := B3DSpotLight new. headLight position: 0@-1@0. headLight target: 0@0@0. headLight lightColor: (B3DMaterialColor color: (Color blue)). headLight attenuation: (B3DLightAttenuation constant: 1.0 linear: 0.0 squared: 0.0). headLight minAngle: 5. headLight maxAngle: 6. scene lights add: headLight. scene objects do: [ :object | object material: nil]! !!AdvancedB3DSceneMorph methodsFor: 'initialization' stamp: 'ti 3/24/2000 17:26'!initialize super initialize. self stepTime: 0. self rotationAngle: 1. self beRotating.! !!AdvancedB3DSceneMorph methodsFor: 'properties' stamp: 'ti 3/24/2000 16:37'!beRotating isRotating := true.! !!AdvancedB3DSceneMorph methodsFor: 'properties' stamp: 'ti 3/24/2000 16:37'!beStill isRotating := false.! !!AdvancedB3DSceneMorph methodsFor: 'properties' stamp: 'ti 3/24/2000 16:37'!isRotating ^isRotating! !!AdvancedB3DSceneMorph methodsFor: 'properties' stamp: 'ti 3/24/2000 16:37'!switchRotationStatus self isRotating ifTrue: [self beStill] ifFalse: [self beRotating]! !!AdvancedB3DSceneMorph methodsFor: 'stepping' stamp: 'ti 3/27/2000 16:55'!step self isRotating ifTrue: [ scene defaultCamera rotateBy: self rotationAngle. self updateHeadlight. self changed.].! !This class implements the alarms for Wonderlands. The user specifies the time the alarm should go off (either in a certain amount of time or at a specific moment) and the task the system should execute when the alarm goes off.!!Alarm methodsFor: 'accessing' stamp: 'jsp 2/1/1999 14:50'!checkTime "Returns the time the alarm is set to go off at" ^ alarmTime.! !!Alarm methodsFor: 'management' stamp: 'jsp 1/29/1999 14:49'!execute "Execute the appointed task because it's the appointed hour" alarmTask value.! !!Alarm methodsFor: 'management' stamp: 'jsp 2/1/1999 12:12'!setScheduler: scheduler "Set the Scheduler that manages this Alarm" myScheduler _ scheduler.! !!Alarm methodsFor: 'management' stamp: 'jsp 2/1/1999 10:58'!setTask: task "Specifies the task the alarm executes when it goes off" alarmTask _ task.! !!Alarm methodsFor: 'management' stamp: 'jsp 2/1/1999 10:59'!setTime: time "Specifies the time the alarm goes off" alarmTime _ time.! !!Alarm methodsFor: 'management' stamp: 'jsp 2/1/1999 16:33'!stop "This method removes the Alarm from myScheduler's list of active Alarms" myScheduler removeAlarm: self.! !!Alarm class methodsFor: 'intialize-release' stamp: 'jsp 2/8/1999 16:07'!do: task at: executeTime inScheduler: scheduler "Creates an alarm that does the specified task at the specified time" | newAlarm | newAlarm _ Alarm new. newAlarm setTime: executeTime. newAlarm setTask: task. newAlarm setScheduler: scheduler. scheduler addAlarm: newAlarm. ^ newAlarm.! !!Alarm class methodsFor: 'intialize-release' stamp: 'jsp 2/8/1999 16:06'!do: task in: waitTime inScheduler: scheduler "This sets an alarm that will expire in waitTime seconds and execute the specified task" | newAlarm | newAlarm _ Alarm new. newAlarm setTask: task. newAlarm setTime: waitTime + (scheduler getTime). newAlarm setScheduler: scheduler. scheduler addAlarm: newAlarm. ^ newAlarm.! !!AliceAbsoluteAnimation methodsFor: 'initialization' stamp: 'jsp 7/20/1999 00:12'!prologue: currentTime "Extends the AliceAbstractAnimation prologue by saving the start state of the animation." undoable ifTrue: [ (myWonderland getUndoStack) push: (AliceUndoAnimation new: (self makeUndoVersion)). ]. (direction = Forward) ifTrue: [ startState _ getStartStateFunction value. lastStartState _ startState. endState _ getEndStateFunction value. ] ifFalse: [ startState _ getStartStateFunction value. endState _ lastStartState. ]. super prologue: currentTime.! !!AliceAbsoluteAnimation methodsFor: 'management' stamp: 'jsp 7/20/1999 00:12'!object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland "This method initializes the animation with all the information that it needs to run." lastStartState _ startFunc value. super object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland.! !!AliceAbsoluteAnimation methodsFor: 'copying' stamp: 'jsp 7/20/1999 00:02'!copy "Creates a copy of the animation" | anim | anim _ AliceAbsoluteAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction style: styleFunction duration: duration undoable: undoable inWonderland: myWonderland. (direction = Forward) ifFalse: [ anim reverseDirection ]. ^ anim.! !!AliceAbsoluteAnimation methodsFor: 'copying' stamp: 'jsp 7/20/1999 00:03'!makeUndoVersion "Creates the undo version of an animation" | anim | anim _ AliceAbsoluteAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction style: styleFunction duration: 0.5 undoable: false inWonderland: myWonderland. anim stop. (direction = Forward) ifTrue: [ anim reverseDirection ]. ^ anim.! !!AliceAbsoluteAnimation methodsFor: 'copying' stamp: 'jsp 7/20/1999 00:07'!reversed "Creates a reversed version of an animation" | anim | anim _ self copy reverseDirection. ^ anim.! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:02'!getAnimatedObject "Return the object that this animation affects" ^ animatedObject.! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:02'!getLoopCount "Returns the animation's current loop count" ^ loopCount.! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:02'!getState "Returns the current state of the animation." ^ state.! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:03'!isDone "Returns true if the animation is running" ^ (state = Stopped).! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:03'!isLooping "Returns true if the animation is looping" ^ ( loopCount > 1) or: [ loopCount = Infinity ].! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:03'!setLoopCount: count "Sets the animation's current loop count" loopCount _ count.! !!AliceAbstractAnimation methodsFor: 'accessing' stamp: 'jsp 7/19/1999 23:03'!setUndoable: aBoolean "Sets the animation's undoable property" undoable _ aBoolean.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:04'!copy self subclassResponsibility.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:04'!epilogue: currentTime "This method does any work that needs to be done after an interation of the animation finishes." (loopCount = Infinity) ifTrue: [state _ Waiting] ifFalse: [ loopCount _ loopCount - 1. (loopCount > 0) ifTrue: [ state _ Waiting ] ifFalse: [state _ Stopped. loopCount _ 1 ]. ].! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:04'!getDuration "This method returns the duration of the animation." ^ duration.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:04'!loop "This method causes an animation to loop forever." loopCount _ Infinity. (state = Stopped) ifTrue: [ state _ Waiting. myScheduler addAnimation: self. ].! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:05'!loop: numberOfTimes "This method causes an animation to loop for the specified number of times." loopCount _ numberOfTimes. (state = Stopped) ifTrue: [ state _ Waiting. myScheduler addAnimation: self. ].! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:05'!looped "This method creates a copy of an animation and loops it forever." | anim | anim _ self copy. anim setLoopCount: Infinity. ^ anim.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:05'!looped: numberOfTimes "This method creates a copy of an animation and loops it for the specified number of times." | anim | anim _ self copy. anim setLoopCount: numberOfTimes. ^ anim.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:05'!pause "This method pauses an active Animation." (state = Running) ifTrue: [ state _ Paused. pausedInterval _ (myScheduler getTime) - startTime.].! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/19/1999 23:07'!prologue: currentTime "This method does any work that needs to be done before the animation starts, including possibly adding the current state to the undo stack." startTime _ currentTime. endTime _ startTime + duration. state _ Running.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/20/1999 01:04'!resume "This method resumes a paused animation" (state = Paused) ifTrue: [ state _ Running. startTime _ (myScheduler getTime) - pausedInterval. endTime _ startTime + duration. ] ifFalse: [(state = Stopped) ifTrue: [ state _ Waiting. myScheduler addUpdateItem: self. ]. ]! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/20/1999 01:10'!start "This method starts an existing animation" state _ Waiting. loopCount _ 1. myScheduler addUpdateItem: self.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/20/1999 01:10'!stop "This method changes the state of an animation to stopped. If it is currently active, the Scheduler will remove it from the list of active animations." state _ Stopped.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/20/1999 01:10'!stopLooping "This method causes the animation to stop looping; the current interation of the animation completes before the animation stops." loopCount _ 1.! !!AliceAbstractAnimation methodsFor: 'management' stamp: 'jsp 7/28/1999 21:51'!update: currentTime "Updates the animation using the current Wonderland time" | newState | (state = Waiting) ifTrue: [self prologue: currentTime]. (state = Running) ifTrue: [ proportionDone _ styleFunction value: (currentTime - startTime) value: duration. newState _ startState interpolateTo: endState at: proportionDone. updateFunction value: newState. (currentTime >= endTime) ifTrue: [ state _ Finished. ]. ]. (state = Finished) ifTrue: [self epilogue: currentTime].! !!AliceAbstractAnimation methodsFor: 'reversing' stamp: 'jsp 7/19/1999 23:01'!reverseDirection "Changes the direction an animation runs in (forward or in reverse)" (direction = Forward) ifTrue: [ direction _ Reverse ] ifFalse: [ direction _ Forward ].! !!AliceAbstractAnimation methodsFor: 'private' stamp: 'jsp 7/19/1999 23:00'!scaleDuration: scaleAmount "Scales the animation's duration by the specified amount" duration _ duration * scaleAmount.! !!AliceAbstractAnimation methodsFor: 'private' stamp: 'jsp 7/19/1999 23:01'!setDirection: aDirection "Sets the animation's direction variable" direction _ aDirection.! !!AliceAbstractAnimation methodsFor: 'initialization' stamp: 'jsp 7/28/1999 21:51'!object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland "This method initializes the Animation with all the information that it needs run." animatedObject _ anObject. updateFunction _ func. styleFunction _ styleFunc. getStartStateFunction _ startFunc. getEndStateFunction _ endFunc. duration _ time. undoable _ canUndo. myScheduler _ aWonderland getScheduler. myWonderland _ aWonderland. loopCount _ 1. direction _ Forward. state _ Waiting. myScheduler addAnimation: self.! !!AliceAbstractAnimation class methodsFor: 'class initialization' stamp: 'jsp 7/19/1999 22:57'!initialize "Initialize the class variables" Waiting _ 1. Running _ 2. Paused _ 3. Finished _ 4. Stopped _ 5. Forward _ 0. Reverse _ 1. Infinity _ -1.! !!AliceAction methodsFor: 'accessing' stamp: 'jsp 7/19/1999 22:06'!getAffectedObject "Returns the object affected by the action" ^ affectedObject.! !!AliceAction methodsFor: 'accessing' stamp: 'jsp 7/19/1999 22:08'!isDone "Returns true if the action is done executing either because it's lifetime has expired or because the specified condition is true" (lifetime > 0) ifTrue: [^ (lifetime < (myScheduler getTime))] ifFalse: [^ (stopCondition value)]. ! !!AliceAction methodsFor: 'accessing' stamp: 'jsp 7/19/1999 22:27'!isPaused "Returns true if the action is paused" ^ paused.! !!AliceAction methodsFor: 'accessing' stamp: 'jsp 7/19/1999 22:28'!pause "Pause the action" paused _ true.! !!AliceAction methodsFor: 'accessing' stamp: 'jsp 7/19/1999 22:28'!resume "resume the action" paused _ false.! !!AliceAction methodsFor: 'management' stamp: 'jsp 7/19/1999 22:29'!setAffectedObject: anObject "Sets the object affected by the action" affectedObject _ anObject.! !!AliceAction methodsFor: 'management' stamp: 'jsp 7/19/1999 22:29'!setLifetime: howlong andCondition: condition "Sets how long the action should run, or the condition under which it should stop" lifetime _ howlong. stopCondition _ condition.! !!AliceAction methodsFor: 'management' stamp: 'jsp 7/19/1999 22:29'!setTask: task "Sets the task the Action should perform each frame" actionTask _ task. paused _ false.! !!AliceAction methodsFor: 'management' stamp: 'jsp 7/19/1999 22:29'!stop "This method removes the Action from myScheduler's list of active actions" stopCondition _ [ true ]. myScheduler removeAction: self.! !!AliceAction methodsFor: 'update' stamp: 'jsp 7/19/1999 22:30'!update: currentTime "Execute the Action's task" paused ifFalse: [ actionTask value ].! !!AliceAction class methodsFor: 'initialize-release' stamp: 'jsp 7/19/1999 22:31'!do: task eachframefor: time toObject: anObject inScheduler: scheduler "Creates a new AliceAction that performs the specified task each frame for (time) seconds" | newAction | newAction _ AliceAction new. newAction setTask: task. newAction setLifetime: (time + (scheduler getTime)) andCondition: [false]. newAction setAffectedObject: anObject. newAction setScheduler: scheduler. scheduler addUpdateItem: newAction. ^ newAction.! !!AliceAction class methodsFor: 'initialize-release' stamp: 'jsp 7/19/1999 22:32'!do: task eachframeuntil: condition toObject: anObject inScheduler: scheduler "Creates a new AliceAction that performs the specified task each frame until the specified condition holds true" | newAction | newAction _ AliceAction new. newAction setTask: task. newAction setLifetime: -1 andCondition: condition. newAction setAffectedObject: anObject. newAction setScheduler: scheduler. scheduler addUpdateItem: newAction. ^ newAction.! !!AliceAction class methodsFor: 'initialize-release' stamp: 'jsp 7/19/1999 22:33'!do: task toObject: anObject inScheduler: scheduler "Creates a new AliceAction that executes the specified task each frame" | newAction | newAction _ AliceAction new. newAction setTask: task. newAction setLifetime: -1 andCondition: [false]. newAction setAffectedObject: anObject. newAction setScheduler: scheduler. scheduler addUpdateItem: newAction. ^ newAction.! !!AliceActor methodsFor: 'initialization' stamp: 'jsp 6/9/1999 00:11'!initializeFor: anAliceWorld "Initialize the instance variables for the AliceActor" super initialize. myName _ 'Unnamed'. myWorld _ myWorld. myParent _ myWorld getScene. myParent addChild: self. "Initialize our material" myMaterial _ B3DMaterial new. myMaterial ambientPart: Color white. myMaterial diffusePart: Color white. myMaterial specularPart: Color white. "Set up our default properties" myColor _ B3DColor4 r: 1.0 g: 1.0 b: 1.0 a: 1.0. compositeMatrix _ B3DMatrix4x4 identity. scaleMatrix _ B3DMatrix4x4 identity. isHidden _ false. isFirstClass _ true.! !!AliceActor methodsFor: 'drawing' stamp: 'jsp 6/9/1999 00:16'!drawMesh: aRenderer "Draw the mesh for this actor." myMaterial ifNotNil: [ aRenderer pushMaterial. aRenderer material: myMaterial. ]. myTexture ifNotNil: [ aRenderer pushTexture. aRenderer texture: myTexture. ]. "Note from Andreas: Using myMesh>>renderOn: here prevents meshes from being picked!!" myMesh ifNotNil: [ myMesh renderOn: aRenderer ]. myTexture ifNotNil: [ aRenderer popTexture ]. myMaterial ifNotNil: [ aRenderer popMaterial ].! !!AliceActor methodsFor: 'drawing' stamp: 'jsp 6/9/1999 00:14'!renderOn: aRenderer "Draw the actor." "Save the old transformation matrix" aRenderer pushMatrix. "Modify the matrix using our composite matrix for position and orientation" aRenderer transformBy: compositeMatrix. "Save the new transformation matrix" aRenderer pushMatrix. "Modify the matrix using our scale matrix - we do this seperately to avoid scaling space" aRenderer transformBy: scaleMatrix. "Draw our mesh if the object is not hidden" (isHidden) ifFalse: [ self drawMesh: aRenderer ]. "Remove the scaling matrix" aRenderer popMatrix. "Draw our children. Note: For correct picking it is important to use B3DRenderEngine>>render: here." myChildren do: [:child | aRenderer render: child]. "Restore the old transformation matrix" aRenderer popMatrix.! !!AliceActor class methodsFor: 'instance creation' stamp: 'jsp 6/9/1999 00:10'!newFor: anAliceWorld "Create a new instance for this World." ^ super new initializeFor: anAliceWorld.! !!AliceActor class methodsFor: 'unique name creation' stamp: 'jsp 6/9/1999 00:09'!uniqueNameFrom: aName "If aName is not an instance variable of this class, returns aName. Otherwise it returns a unique name based on aName that is not an instance var." | index | (self instVarNames includes: aName) ifFalse: [ ^ aName ]. index _ 2. [ self instVarNames includes: (aName , (index asString)) ] whileTrue: [ index _ index + 1 ]. ^ aName , (index asString). ! !!AliceAlarm methodsFor: 'accessing' stamp: 'jsp 7/19/1999 21:17'!checkTime "Returns the time the alarm is set to go off at" ^ alarmTime.! !!AliceAlarm methodsFor: 'accessing' stamp: 'jsp 7/20/1999 01:06'!isDone "Returns true if the alarm has expired." ^ (myScheduler getTime) > alarmTime.! !!AliceAlarm methodsFor: 'management' stamp: 'jsp 7/20/1999 01:06'!setTask: task "Specifies the task the alarm executes when it goes off. Also sets isDone to false because the task has not yet been executed." alarmTask _ task.! !!AliceAlarm methodsFor: 'management' stamp: 'jsp 7/19/1999 21:21'!setTime: time "Specifies the time the alarm goes off" alarmTime _ time.! !!AliceAlarm methodsFor: 'management' stamp: 'jsp 7/20/1999 01:06'!stop "This method stops the alarm." myScheduler removeUpdateItem: self.! !!AliceAlarm methodsFor: 'update' stamp: 'jsp 7/20/1999 01:06'!update: currentTime "If the alarm's time has expired, then execute the task associated with the alarm." (alarmTime < currentTime) ifTrue: [ self execute ].! !!AliceAlarm class methodsFor: 'instance creation' stamp: 'jsp 7/19/1999 22:00'!do: task at: executeTime inScheduler: scheduler "Creates an alarm that does the specified task at the specified time" | newAlarm | newAlarm _ AliceAlarm new. newAlarm setTime: executeTime. newAlarm setTask: task. newAlarm setScheduler: scheduler. scheduler addUpdateItem: newAlarm. ^ newAlarm.! !!AliceAlarm class methodsFor: 'instance creation' stamp: 'jsp 7/19/1999 22:01'!do: task in: waitTime inScheduler: scheduler "This sets an alarm that will expire in waitTime seconds and execute the specified task" | newAlarm | newAlarm _ AliceAlarm new. newAlarm setTask: task. newAlarm setTime: waitTime + (scheduler getTime). newAlarm setScheduler: scheduler. scheduler addAlarm: newAlarm. ^ newAlarm.! !!AliceHierarchical methodsFor: 'initialization' stamp: 'jsp 6/8/1999 23:52'!initialize "Initialize this instance" myChildren _ OrderedCollection new.! !!AliceHierarchical methodsFor: 'parent-child' stamp: 'jsp 6/8/1999 23:57'!getAllChildren "Return all of this instance's children" | children | children _ OrderedCollection new. myChildren do: [:child | children addLast: child. children _ children , (child getAllChildren). ]. ^ children.! !!AliceHierarchical methodsFor: 'parent-child' stamp: 'jsp 6/8/1999 23:58'!getChildren "Return the object's immediate children." ^ (myChildren copy).! !!AliceHierarchical methodsFor: 'parent-child' stamp: 'jsp 6/8/1999 23:59'!getParent "Return the object's parent." ^ myParent.! !!AliceHierarchical methodsFor: 'parent-child' stamp: 'jsp 6/8/1999 23:59'!setParent: anObject "Set this instance's parent" myParent _ anObject.! !!AliceHierarchical methodsFor: 'private' stamp: 'jsp 6/8/1999 23:54'!addChild: aChild "Add an object to this instance's list of children. Checks to make sure that aChild is not already a child of this object" ((myChildren identityIndexOf: aChild) = 0) ifTrue: [ myChildren addLast: aChild ].! !!AliceHierarchical methodsFor: 'private' stamp: 'jsp 6/8/1999 23:59'!appendChildrenNamesTo: prefix "Return the object's children's names, each appended to the prefix." | nameList | nameList _ OrderedCollection new. myChildren do: [:child | nameList addLast: (prefix , (child getName)). nameList _ nameList , (child appendChildrenNamesTo: (prefix , ' '))]. ^ nameList.! !!AliceHierarchical methodsFor: 'private' stamp: 'jsp 6/8/1999 23:58'!getChildrenNames "Return the object's children." ^ myChildren collect: [: child | child asString ].! !!AliceHierarchical methodsFor: 'private' stamp: 'jsp 6/8/1999 23:57'!removeChild: aChild "Remove an object from this instance's list of children" myChildren remove: aChild ifAbsent: [].! !!AliceHierarchical class methodsFor: 'instance creation' stamp: 'jsp 6/8/1999 23:52'!new "Create and initialize a new instance." ^ super new initialize.! !!AliceNamespace methodsFor: 'initialize' stamp: 'jsp 6/7/1999 21:49'!initialize "Initialize the namespace" myDictionary _ AliceConstants copy. myWorkspace _ Workspace new. myWorkspace setBindings: myDictionary. myWorkspace embeddedInMorphicWindowLabeled: 'Namespace'.! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/7/1999 21:43'!at: key "Return the value in the namespace associated with the key" ^ myDictionary at: key.! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/7/1999 21:43'!at: key put: value "Store the value in the namespace under the key" myDictionary at: key put: value.! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/7/1999 21:42'!getDictionary "Return the namespace dictionary" ^ myDictionary.! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/7/1999 21:44'!getEvaluationContext "Return a context containing the namespace for evaluating a statement " ^ (myWorkspace dependents last select model: myWorkspace).! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/8/1999 21:55'!includesKey: aKey "Return true if the namespace includes the key" ^ myDictionary includesKey: aKey.! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/8/1999 22:57'!removeKey: theKey "Remove the key from the namespace" myDictionary removeKey: theKey ifAbsent: [].! !!AliceNamespace methodsFor: 'accessing' stamp: 'jsp 6/8/1999 22:57'!removeKey: theKey ifAbsent: failBlock "Remove the key from the namespace. If the key isn't there, run the code in the fail block." myDictionary removeKey: theKey ifAbsent: failBlock.! !!AliceNamespace class methodsFor: 'instance creation' stamp: 'jsp 6/7/1999 21:46'!new "Create a new namespace for an Alice world" ^ super new initialize.! !!AlicePoolDefiner class methodsFor: 'class initialization' stamp: 'jsp 6/7/1999 14:58'!initialize "Initialize the Alice 2.0 pool dictionary" self initPool.! !!AlicePoolDefiner class methodsFor: 'pool definition' stamp: 'jsp 6/29/1999 00:06'!initPool "Create the pool dictionary if necessary" | poolName | poolName _ #AliceConstants. (Smalltalk includesKey: poolName) ifFalse:[ Smalltalk declare: poolName from: Undeclared. ]. (Smalltalk at: poolName) isNil ifTrue:[ (Smalltalk associationAt: poolName) value: ((Smalltalk at: #WonderlandConstants) copy). ]. self initPool: (Smalltalk at: poolName).! !!AlicePoolDefiner class methodsFor: 'pool definition' stamp: 'jsp 6/7/1999 15:03'!initPool: aDictionary "Initialize the dictionary" aDictionary at: #inOrder put: #inOrder. aDictionary at: #together put: #together.! !!AliceRelativeAnimation methodsFor: 'initialization' stamp: 'jsp 7/20/1999 00:15'!object: anObject update: func getStartState: startFunc getEndState: endFunc getReverseState: reverseFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland "This method initializes the Animation with all the information that it needs to run." getReverseStateFunction _ reverseFunc. super object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland.! !!AliceRelativeAnimation methodsFor: 'management' stamp: 'jsp 7/20/1999 00:18'!prologue: currentTime "Extends the AbstractAnimation prologue by saving the start state of the animation." undoable ifTrue: [ (myWonderland getUndoStack) push: (AliceUndoAnimation new: (self makeUndoVersion)). ]. (direction = Forward) ifTrue: [ startState _ getStartStateFunction value. endState _ getEndStateFunction value. ] ifFalse: [ startState _ getStartStateFunction value. endState _ getReverseStateFunction value. ]. super prologue: currentTime.! !!AliceRelativeAnimation methodsFor: 'copying' stamp: 'jsp 7/20/1999 00:16'!copy "Creates a copy of the animation" | anim | anim _ AliceRelativeAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction getReverseState: getReverseStateFunction style: styleFunction duration: duration undoable: undoable inWonderland: myWonderland. (direction = Forward) ifFalse: [ anim reverseDirection ]. ^ anim.! !!AliceRelativeAnimation methodsFor: 'copying' stamp: 'jsp 7/20/1999 00:18'!makeUndoVersion "Creates the undo version of an animation" | anim | anim _ AliceRelativeAnimation new. anim object: animatedObject update: updateFunction getStartState: getStartStateFunction getEndState: getEndStateFunction getReverseState: getReverseStateFunction style: styleFunction duration: 0.5 undoable: false inWonderland: myWonderland. anim stop. (direction = Forward) ifTrue: [ anim reverseDirection ]. ^ anim.! !!AliceRelativeAnimation methodsFor: 'copying' stamp: 'jsp 7/20/1999 00:18'!reversed "Creates a reversed version of an animation" | anim | anim _ self copy reverseDirection. ^ anim.! !!AliceScheduler methodsFor: 'initialize' stamp: 'jsp 6/7/1999 16:06'!initialize "Initialize the scheduler" "The scheduler starts at time 0" currentTime _ 0. elapsedTime _ 0. "The scheduler starts executing at 1:1 time" speed _ 1. "The scheduler starts running" isRunning _ true. "Determine the system time we're starting at" lastSystemTime _ Time millisecondClockValue / 1000.0. "Create the list of items to update" updateList _ OrderedCollection new.! !!AliceScheduler methodsFor: 'initialize' stamp: 'jsp 6/7/1999 15:51'!reset "Resets the Wonderland time to 0" self initialize.! !!AliceScheduler methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:53'!getElapsedTime "Returns the time that elapsed in the last Scheduler tick" ^ elapsedTime.! !!AliceScheduler methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:53'!getFPS "Returns the instantaneous frames per second (1 / elapsedTime)" ^ (1.0 / elapsedTime).! !!AliceScheduler methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:53'!getTime "Returns the current scheduler time" ^ currentTime.! !!AliceScheduler methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:55'!pause "Pause the scheduler. Pauses all script executiong, but any active cameras continue to render." isRunning _ false.! !!AliceScheduler methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:55'!resume "If the scheduler was paused, resume it." isRunning ifFalse: [ isRunning _ true. lastSystemTime _ (Time millisecondClockValue) / 1000.0. ].! !!AliceScheduler methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:55'!setSpeed: newSpeed "This method sets the speed for the Scheduler. 1 is a 1:1 mapping with clock time, 2 is a 2:1 mapping, etc." (speed > 0) ifTrue: [speed _ newSpeed] ifFalse: [self error: 'Scheduler speed must be greater than 0.'].! !!AliceScheduler methodsFor: 'update list maintenance' stamp: 'jsp 6/7/1999 16:05'!addUpdateItem: newItem "Add a new item to the scheduler's update list (a running animation, active script, etc" updateList addLast: newItem.! !!AliceScheduler methodsFor: 'update list maintenance' stamp: 'jsp 6/7/1999 16:06'!removeUpdateItem: anItem "Add a new item to the scheduler's update list (a running animation, active script, etc)" updateList remove: anItem ifAbsent: [].! !!AliceScheduler methodsFor: 'ticking' stamp: 'jsp 6/7/1999 16:02'!tick "Figure out how much time has elapsed since the last Scheduler tick and update all the scripts" isRunning ifTrue: [ elapsedTime _ ((Time millisecondClockValue / 1000.0) - lastSystemTime) * speed. "if elapsedTime is negative the clock rolled over; deal with it" (elapsedTime < 0) ifTrue: [lastSystemTime _ 0. elapsedTime _ (Time millisecondClockValue) / 1000.0]. currentTime _ currentTime + elapsedTime. lastSystemTime _ lastSystemTime + elapsedTime. "Process scripts here" updateList do: [:item | item update: currentTime. (item isDone) ifTrue: [self removeUpdateItem: item] ]. ].! !!AliceScheduler class methodsFor: 'instance creation' stamp: 'jsp 6/7/1999 15:46'!new "Create a new scheduler and initialize it" ^ super new initialize.! !!AliceScript methodsFor: 'initialize' stamp: 'jsp 7/20/1999 01:08'!initialize: anAliceWorld "Initialize script by assigning the scheduler and putting default values in the instance variables" "Set the script name" scriptName _ 'Unnamed'. "Set the scheduler for this script" myWorld _ anAliceWorld. myScheduler _ myWorld getScheduler. "By default a script contains no commands" myCommands _ OrderedCollection new. "By default there are no active commands" pendingCommands _ OrderedCollection new. "By default there are no active animations" activeAnimations _ OrderedCollection new. "By default scripts run in order (one command after another)" scriptType _ inOrder. "By default the script isn't running" isRunning _ false.! !!AliceScript methodsFor: 'accessing' stamp: 'jsp 6/7/1999 21:59'!getScriptName "Returns the name of the script" ^ scriptName.! !!AliceScript methodsFor: 'accessing' stamp: 'jsp 6/7/1999 16:12'!isDone "Returns true if the script is not currently running" ^ isRunning not.! !!AliceScript methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:15'!setCommands: commands "Set the commands in the script" myCommands _ commands.! !!AliceScript methodsFor: 'accessing' stamp: 'jsp 6/7/1999 21:59'!setScriptName: aName "Sets the name of the script" scriptName _ aName.! !!AliceScript methodsFor: 'accessing' stamp: 'jsp 6/7/1999 15:14'!setScriptType: type "Set the script type (inOrder or Together)" scriptType _ type.! !!AliceScript methodsFor: 'executing' stamp: 'jsp 7/20/1999 01:09'!start "Start running this script" | result | (scriptType = inOrder) ifTrue: [ pendingCommands _ OrderedCollection new. 1 to: (myCommands size) do: [:i | pendingCommands addLast: i ]. ] ifFalse: [ myCommands do: [:command | result _ command. result _ Compiler new evaluate: command in: nil to: nil notifying: (myWorld getNamespace getEvaluationContext) ifFail: []. myWorld addOutputText: (result printString). (result isKindOf: Animation) ifTrue: [ activeAnimations add: result ]. ]. ]. isRunning _ true. "Need to add this script to the scheduler so it gets updated" myScheduler addUpdateItem: self. "Update the script once with the current time" self update: (myScheduler getTime).! !!AliceScript methodsFor: 'executing' stamp: 'jsp 6/7/1999 21:38'!update: currentTime "Determine how to update this script based on the type of script it is" (scriptType = inOrder) ifTrue: [ self updateInOrder: currentTime ] ifFalse: [ self updateTogether: currentTime ].! !!AliceScript methodsFor: 'executing' stamp: 'jsp 6/8/1999 17:33'!updateInOrder: currentTime "Update this script assuming that one command runs after the previous command finishes" | nextCommand result | "Update the previous command if it's still active" activeAnimations do: [:anim | anim update: currentTime. (anim isDone) ifTrue: [activeAnimations remove: anim ]]. "Check if all active animations are complete, if not keep pulling and executing script commands until we hit one that doesn't complete immediately" (activeAnimations isEmpty) ifTrue: [ [ (pendingCommands isEmpty) or: [activeAnimations isEmpty not] ] whileFalse: [ nextCommand _ myCommands at: (pendingCommands removeFirst). "evaluate the command in my namespace" result _ Compiler new evaluate: nextCommand in: nil to: nil notifying: (myWorld getNamespace getEvaluationContext) ifFail: []. myWorld addOutputText: (result printString). (result isKindOf: Animation) ifTrue: [ activeAnimations addLast: result ]. ]. ((activeAnimations isEmpty) and: [ pendingCommands isEmpty ]) ifTrue: [ isRunning _ false ]. ].! !!AliceScript methodsFor: 'executing' stamp: 'jsp 6/7/1999 21:39'!updateTogether: currentTime "Update this script assuming that all script commands begin simultaneously" activeAnimations do: [:anim | anim update: currentTime. (anim isDone) ifTrue: [activeAnimations remove: anim ]]. (activeAnimations isEmpty) ifTrue: [ isRunning _ false ].! !!AliceScript class methodsFor: 'instance creation' stamp: 'jsp 6/8/1999 13:36'!new: type withCommands: commands in: anAliceWorld "Create a new nameless (lambda) script containing the specified commands" | newScript | newScript _ AliceScript new initialize: anAliceWorld. newScript setScriptType: type. newScript setCommands: commands. ^ newScript.! !!AliceTextOutputWindow methodsFor: 'initialization' stamp: 'jsp 7/25/1999 23:11'!initialize "Initialize the window for output." super initialize. self color: (Color r: 0.627 g: 0.909 b: 0.972). self openInWorld.! !!AliceTextOutputWindow methodsFor: 'output text' stamp: 'jsp 7/25/1999 23:09'!addText: aString "Adds the specified string to the output window" | textLength | self setText: ((textMorph contents) , aString) asText. textLength _ textMorph contents size + 1. self selectFrom: textLength to: textLength. self scrollSelectionIntoView.! !!AliceTextOutputWindow methodsFor: 'output text' stamp: 'jsp 7/25/1999 23:05'!addTextOnNewLine: aString "Adds the specified string to the output window as a new line" | textLength | self setText: ((textMorph contents) , (Character cr asString) , aString) asText. textLength _ textMorph contents size + 1. self selectFrom: textLength to: textLength. self scrollSelectionIntoView.! !!AliceUndoAnimation methodsFor: 'accessing' stamp: 'jsp 7/20/1999 00:10'!setAnimation: anAnimation "Set wrapped animation." wrappedAnimation _ anAnimation.! !!AliceUndoAnimation methodsFor: 'undoing' stamp: 'jsp 7/20/1999 00:10'!undoIt "Undo by running the wrapped animation." wrappedAnimation start.! !!AliceUndoAnimation class methodsFor: 'instance creation' stamp: 'jsp 7/20/1999 00:11'!new: anAnimation "Create a wrapper for undoing an animation" | newUndo | newUndo _ UndoAnimation new. newUndo setAnimation: anAnimation. ^ newUndo.! !!AliceUpdateable methodsFor: 'management' stamp: 'jsp 7/20/1999 00:59'!setScheduler: scheduler "Set the Scheduler that manages this updateable item" myScheduler _ scheduler.! !!AliceUpdateable class methodsFor: 'instance creation' stamp: 'jsp 7/19/1999 21:54'!new "Create and initialize a new instance" super new initialize.! !!AliceWorld methodsFor: 'temporary' stamp: 'jsp 6/8/1999 22:52'!makeActorFrom: filename "Creates a new actor using the specification from the given file" | aFile words line startSubstr index parent name texture meshFile matrix baseActor newActor protoClass actorClass fileVersion | myUndoStack closeStack. words _ (filename findTokens: #.). ((words last) = 'mdl') ifTrue: [ aFile _ (CrLfFileStream readOnlyFileNamed: filename) ascii. "First see if we need to create a prototype class for this model" (ActorPrototypeClasses includesKey: (aFile localName)) ifTrue: [ protoClass _ ActorPrototypeClasses at: (aFile localName) ] ifFalse: [ "Make a new prototype class for this model" protoClass _ (WonderlandActor newUniqueClassInstVars: '' classInstVars: ''). ActorPrototypeClasses at: (aFile localName) put: protoClass. ]. "Check what version this mdl file is" line _ aFile upTo: (Character cr). line _ aFile upTo: (Character cr). line _ aFile upTo: (Character cr). ((line truncateTo: 7) = 'version') ifTrue: [ fileVersion _ 1 ] ifFalse: [ fileVersion _ 0 ]. [ line _ aFile upTo: (Character cr). (aFile atEnd) ifTrue: [ true ] ifFalse: [ words _ line findTokens: '='. false ] ] whileFalse: [ "See if we're creating a new object" (((words size) > 1) and: [ ((words at: 2) beginsWith: ' _MakeObject') or: [ (words at: 2) beginsWith: ' Alice.MakeObject' ] ]) ifTrue: [ (fileVersion = 0) ifTrue: [ words _ line findTokens: #,. parent _ (words at: 2) withBlanksTrimmed. name _ (((words at: 3) withBlanksTrimmed) findBetweenSubStrs: '"') at: 1. ] ifFalse: [ name _ (words at: 1) truncateTo: (((words at: 1) size) - 1). parent _ ((words at: 3) findTokens: #,) at: 1. ]. "Now pull in the texture to use" startSubstr _ name , '.SetTexture'. [(line _ aFile upTo: (Character cr)) beginsWith: startSubstr] whileFalse: []. texture _ (line findBetweenSubStrs: '"') at: 2. texture _ (aFile directory pathName), FileDirectory slash, texture. "Read the composite matrix to use" startSubstr _ name , '._SetLocalTransformation'. [(line _ aFile upTo: (Character cr)) beginsWith: startSubstr] whileFalse: []. matrix _ B3DMatrix4x4 new. words _ line findBetweenSubStrs: ',()'. words removeAllSuchThat: [:str | str = ' ']. index _ words size. 4 to: 1 by: -1 do: [:i | 4 to: 1 by: -1 do: [:j | matrix at: i at: j put: ((words at: index) withBlanksTrimmed) asNumber. index _ index - 1. ]. ]. 1 to: 4 do: [:i | index _ matrix at: i at: 4. matrix at: i at: 4 put: (matrix at: 4 at: i). matrix at: 4 at: i put: index. ]. matrix a14: (matrix a14 negated). "Read the mesh file to use" startSubstr _ 'LoadGeometry'. [(line _ aFile upTo: (Character cr)) beginsWith: startSubstr] whileFalse: []. meshFile _ (line findBetweenSubStrs: '"') at: 2. meshFile _ (aFile directory pathName), FileDirectory slash, meshFile. "Now build the actor name" words _ name findTokens: '.'. name _ words last. name at: 1 put: ((name at: 1) asLowercase). "Now build the parent name" parent _ parent copyReplaceAll: '.' with: ' '. "Now create the object" (parent = 'None') ifTrue: [ actorClass _ protoClass newUniqueClassInstVars: '' classInstVars: ''. baseActor _ actorClass createFor: self. actorClassList addLast: actorClass. baseActor setName: name. baseActor setTexture: texture. baseActor loadMeshFromFile: meshFile. baseActor setComposite: matrix. ] "end base actor creation" ifFalse: [ actorClass _ WonderlandActor newUniqueClassInstVars: '' classInstVars: ''. newActor _ actorClass createFor: self. actorClassList addLast: actorClass. newActor setName: name. parent _ (baseActor getChildNamed: parent). newActor reparentTo: parent. newActor becomePart. newActor setTexture: texture. newActor loadMeshFromFile: meshFile. newActor setComposite: matrix. ]. "end new actor with parent" ]. "end MakeObject parsing" ]. "end file parsing" aFile close. myUndoStack openStack. "Ensure that the new actor's name is unique" name _ self uniqueNameFrom: (baseActor getName). baseActor setName: name. myNamespace at: name put: baseActor. "Add an undo item to undo the creation of this object" myUndoStack push: (UndoAction new: [ baseActor removeFromScene. myNamespace removeKey: name ifAbsent: []. ] ). ^ baseActor. ]. " end mdl file parsing"! !!AliceWorld methodsFor: 'temporary' stamp: 'jsp 6/8/1999 23:06'!makeLight "Create a light of the specified type and add it to the Wonderland" | theLight lightType name | lightType _ positional. "Make sure the user gave us a type of light" [ WonderlandVerifier VerifyLight: lightType ] ifError: [ :msg :rcvr | self reportErrorToUser: 'Squeak could not determine the type of light to create because ', msg. ^ nil ]. "The user gave us a valid type type, so proceed" (lightType = ambient) ifTrue: [ theLight _ WonderlandAmbientLight createFor: self. ] ifFalse: [ (lightType = positional) ifTrue: [ theLight _ WonderlandPositionalLight createFor: self. ] ifFalse: [ (lightType = directional) ifTrue: [ theLight _ WonderlandDirectionalLight createFor: self. ] ifFalse: [ theLight _ WonderlandSpotLight createFor: self. ] ] ]. name _ self uniqueNameFrom: 'light'. theLight setName: name. myNamespace at: name put: theLight. lightList addLast: theLight. ^ theLight.! !!AliceWorld methodsFor: 'temporary' stamp: 'jsp 6/8/1999 23:05'!makeLight: lightType "Create a light of the specified type and add it to the Wonderland" | theLight name | "Make sure the user gave us a type of light" [ WonderlandVerifier VerifyLight: lightType ] ifError: [ :msg :rcvr | self reportErrorToUser: 'Squeak could not determine the type of light to create because ', msg. ^ nil ]. "The user gave us a valid type type, so proceed" (lightType = ambient) ifTrue: [ theLight _ WonderlandAmbientLight createFor: self. ] ifFalse: [ (lightType = positional) ifTrue: [ theLight _ WonderlandPositionalLight createFor: self. ] ifFalse: [ (lightType = directional) ifTrue: [ theLight _ WonderlandDirectionalLight createFor: self. ] ifFalse: [ theLight _ WonderlandSpotLight createFor: self. ] ] ]. name _ self uniqueNameFrom: 'light'. theLight setName: name. myNamespace at: name put: theLight. lightList addLast: theLight. ^ theLight.! !!AliceWorld methodsFor: 'temporary' stamp: 'jsp 6/8/1999 22:51'!renderWonderland: aRenderer "Temporary method" self renderWorld: aRenderer.! !!AliceWorld methodsFor: 'initialize-reset-release' stamp: 'jsp 7/25/1999 23:10'!initialize "Initialize the Alice world" | defaultCamera | "Initialize this Wonderland's shared namespace" myNamespace _ AliceNamespace new. myNamespace at: 'world' put: self. "Create the Wonderland's scheduler" myScheduler _ AliceScheduler new. myNamespace at: 'scheduler' put: myScheduler. "Initialize the list of actor UniClasses" actorClassList _ OrderedCollection new. "Initialize the shared mesh and texture directories" sharedMeshDict _ Dictionary new. sharedTextureDict _ Dictionary new. "Create an output window for us to dump text to" myTextOutputWindow _ AliceTextOutputWindow new. myTextOutputWindow setText: 'Squeak Alice v2.0.'. cameraList _ OrderedCollection new. lightList _ OrderedCollection new. "-------------------------------" "Create the undo stack for this Wonderland." myUndoStack _ WonderlandUndoStack new. "The scene object is the root of the object tree - all objects in the Wonderland are children (directly or indirectly) of the scene. " myScene _ WonderlandScene newFor: self. myNamespace at: 'scene' put: myScene. "Create the default camera" defaultCamera _ WonderlandCamera createFor: self. cameraList addLast: defaultCamera. myNamespace at: 'camera' put: defaultCamera. myNamespace at: 'cameraWindow' put: (defaultCamera getMorph). defaultCamera setName: 'camera'. myUndoStack reset.! !!AliceWorld methodsFor: 'initialize-reset-release' stamp: 'jsp 6/8/1999 22:46'!release "This method cleans up the world." "Clean up any uniclasses we created" actorClassList do: [:aClass | aClass removeFromSystem ]. "Clean up the output window" myTextOutputWindow delete. "Get rid of our cameras" cameraList do: [:camera | camera release].! !!AliceWorld methodsFor: 'initialize-reset-release' stamp: 'jsp 6/8/1999 17:19'!reset "Reset this Wonderland" "Initialize this Wonderland's shared namespace" myNamespace _ AliceNamespace new. "Reset the scheduler" myScheduler reset. "Reset the shared mesh and texture directories" sharedMeshDict _ Dictionary new. sharedTextureDict _ Dictionary new. "Reset the list of actor uniclasses" actorClassList do: [:aClass | aClass removeFromSystem ]. actorClassList _ OrderedCollection new. "Rebuild the namespace" myNamespace at: 'scheduler' put: myScheduler. myNamespace at: 'world' put: self. "Create a new text output window" myTextOutputWindow setText: 'Reset'.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 22:55'!getActorClassList "Return the list of actor classes" ^ actorClassList.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 22:39'!getCameras "Return the list of cameras in the scene" ^ cameraList.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 21:36'!getDefaultCamera "Return the default camera, which is the camera at the front of the camera list" ^ cameraList first.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 22:39'!getLights "Return the list of lights in the scene" ^ lightList.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 17:38'!getNamespace "Return this world's namespace" ^ myNamespace.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 21:37'!getScene "Return the world's scene" ^ myScene.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 17:56'!getScheduler "Return this world's scheduler" ^ myScheduler.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 21:47'!getSharedMeshDict "Return the shared mesh dictionary" ^ sharedMeshDict.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 21:47'!getSharedTextureDict "Return the shared texture dictionary" ^ sharedTextureDict.! !!AliceWorld methodsFor: 'accessing' stamp: 'jsp 6/8/1999 21:38'!getUndoStack "Return the world's undo stack" ^ myUndoStack.! !!AliceWorld methodsFor: 'creating scripts' stamp: 'jsp 6/8/1999 13:37'!doInOrder: commands "Create a nameless inOrder script with the specified commands" ^ AliceScript new: inOrder withCommands: commands in: self.! !!AliceWorld methodsFor: 'creating scripts' stamp: 'jsp 6/8/1999 13:37'!doTogether: commands "Create a nameless together script with the specified commands" ^ AliceScript new: together withCommands: commands in: self.! !!AliceWorld methodsFor: 'creating actors' stamp: 'jsp 6/8/1999 23:12'!fixNameFrom: aString "Fix the name to be a valid Smalltalk name (e.g., so that we can compile it as an inst var and accessor message)" | aName | aName _ aString select: [:c | c isAlphaNumeric]. "If the name is empty use 'unknown'" aName isEmpty ifTrue:[aName _ 'unknown']. "Make sure the first letter is lowercase" aName first isUppercase ifTrue: [aName _ (aName first asLowercase asString) , (aName copyFrom: 2 to: aName size) ]. "Make sure the first letter is a letter, otherwise use 'a' as the first letter" aName first isLetter ifFalse: [aName _ 'a' , aName]. ^ aName.! !!AliceWorld methodsFor: 'creating actors' stamp: 'jsp 6/8/1999 23:12'!uniqueNameFrom: aString "If aName is unique to this world's namespace, returns that name. Otherwise creates a unique variant and returns that." | index aName | aName _ self fixNameFrom: aString. (myNamespace includesKey: aName) ifFalse: [ ^ aName ] ifTrue: [ index _ 2. [ myNamespace includesKey: (aName , (index asString)) ] whileTrue: [ index _ index + 1 ]. ^ aName , (index asString). ].! !!AliceWorld methodsFor: 'user feedback' stamp: 'jsp 6/8/1999 17:20'!addOutputText: thisText "Appends the given text to the Alice output window" myTextOutputWindow addTextOnNewLine: thisText.! !!AliceWorld methodsFor: 'user feedback' stamp: 'jsp 6/8/1999 21:52'!reportErrorToUser: errorString "When any object in an Alice World discovers an error it creates an error report and then calls this method to display the error to the user." | errWin tm | errWin _ SystemWindowWithButton labelled: 'Ooops'. errWin openInWorldExtent: 400@100. errWin color: (Color white). tm _ TextMorph new. tm initialize. errWin addMorph: tm. tm color: (Color red). tm contents: errorString wrappedTo: 380. tm position: ((errWin position) + (10@20)). tm lock. errWin height: (tm height) + 30. errorSound play.! !!AliceWorld methodsFor: 'undoing actions' stamp: 'jsp 6/8/1999 21:52'!undo "Undo the last action the user performed in the Wonderland. This pulls a block context off the animation stack and executes it." myUndoStack popAndUndo.! !!AliceWorld methodsFor: 'drawing' stamp: 'jsp 6/8/1999 21:48'!renderWorld: aRenderer "Tell all the objects in the World to render themselves." myScene renderOn: aRenderer.! !!AliceWorld methodsFor: 'private' stamp: 'jsp 6/8/1999 22:42'!getTextOutputWindow "Returns the current text output window" ^ myTextOutputWindow.! !!AliceWorld class methodsFor: 'instance creation' stamp: 'jsp 6/7/1999 22:27'!new "AliceWorld new" "Create and initialize a new AliceWorld." B3DPrimitiveEngine isAvailable ifFalse: [ (self confirm: 'WARNING: This Squeak does not have real 3D support.Opening a Wonderland will EXTREMELY time consuming.Are you sure you want to do this?(NO is probably the right answer :-)') ifFalse: [^ self]]. Display depth < 8 ifTrue: [(self confirm: 'The display depth should be set to at least 8 bit.Shall I do this now for you?') ifTrue: [Display newDepth: 8]]. ^ super new initialize.! !!AliceWorld class methodsFor: 'class initialization' stamp: 'jsp 6/7/1999 22:17'!initialize "Initialize the AliceWorld class by creating the ActorPrototypeClasses collection" ActorPrototypeClasses _ Dictionary new.! !!AliceWorld class methodsFor: 'actor prototype mgmt' stamp: 'jsp 6/7/1999 22:18'!removeActorPrototypesFromSystem "Clean out all the actor prototypes - this involves removing those classes from the Smalltalk dictionary" ActorPrototypeClasses do: [:aClass | aClass removeFromSystem ]. ActorPrototypeClasses _ Dictionary new.! !!AlignmentMorph methodsFor: 'initialization' stamp: 'sw 10/24/1998 14:25'!addUpDownArrowsFor: aMorph "Add a column of up and down arrows that serve to send upArrowHit and downArrowHit to aMorph when they're pressed/held down" | holder downArrow upArrow | holder _ Morph new extent: 16 @ 16; beTransparent. downArrow _ ImageMorph new image: (ScriptingSystem formAtKey: 'DownArrow'). upArrow _ ImageMorph new image: (ScriptingSystem formAtKey: 'UpArrow'). upArrow position: holder bounds topLeft + (2@2). downArrow align: downArrow bottomLeft with: holder topLeft + (0 @ TileMorph defaultH) + (2@-2). holder addMorph: upArrow. holder addMorph: downArrow. self addMorphBack: holder. upArrow on: #mouseStillDown send: #upArrowHit to: aMorph. downArrow on: #mouseStillDown send: #downArrowHit to: aMorph.! !!AlignmentMorph methodsFor: 'initialization'!initialize super initialize. borderWidth _ 0. orientation _ #horizontal. "#horizontal or #vertical or #free" centering _ #topLeft. "#topLeft, #center, or #bottomRight" hResizing _ #spaceFill. "#spaceFill, #shrinkWrap, or #rigid" vResizing _ #spaceFill. "#spaceFill, #shrinkWrap, or #rigid" inset _ 2. "pixels inset within owner's bounds" minCellSize _ 0. "minimum space between morphs; useful for tables" layoutNeeded _ true. color _ Color r: 0.8 g: 1.0 b: 0.8.! !!AlignmentMorph methodsFor: 'initialization' stamp: 'djp 10/24/1999 17:13'!openInWindowLabeled: aString inWorld: aWorld inset _ 0. ^super openInWindowLabeled: aString inWorld: aWorld.! !!AlignmentMorph methodsFor: 'accessing' stamp: 'panda 4/25/2000 15:44'!configureForKids self disableDragNDrop. super configureForKids! !!AlignmentMorph methodsFor: 'geometry' stamp: 'di 11/26/1999 22:16'!layoutChanged layoutNeeded ifTrue: [^ self]. "In process." layoutNeeded _ true. priorFullBounds _ fullBounds. "Remember fullBounds" super layoutChanged.! !!AlignmentMorph methodsFor: 'dropping/grabbing' stamp: 'panda 4/25/2000 15:47'!rootForGrabOf: aMorph | root | self dragNDropEnabled ifFalse: [^ super rootForGrabOf: aMorph]. root _ aMorph. [root == self] whileFalse: [root owner = self ifTrue: [^ root]. root _ root owner]. ^ super rootForGrabOf: aMorph! !!AlignmentMorph methodsFor: 'layout' stamp: 'di 11/26/1999 21:37'!fullBounds "This is the hook that triggers lazy re-layout of layout morphs. It works because layoutChanged clears the fullBounds cache. Once per cycle, the fullBounds is requested from every morph in the world, and that request gets propagated through the entire submorph hierarchy, causing re-layout where needed. Note that multiple layoutChanges to the same morph can be done with little cost, since the layout is only done when the morph needs to be displayed." fullBounds ifNil: [ self resizeIfNeeded. self fixLayout. super fullBounds. "updates cache" priorFullBounds == nil ifTrue: [self invalidRect: fullBounds] ifFalse: [fullBounds = priorFullBounds ifFalse: ["report change due to layout" self invalidRect: (fullBounds merge: priorFullBounds)]]. layoutNeeded _ false]. ^ super fullBounds! !!AlignmentMorph methodsFor: 'menu' stamp: 'panda 4/25/2000 15:47'!addCustomMenuItems: aCustomMenu hand: aHandMorph super addCustomMenuItems: aCustomMenu hand: aHandMorph. aCustomMenu add: 'orientation...' action: #chooseOrientation. aCustomMenu add: (self dragNDropEnabled ifTrue: ['close'] ifFalse: ['open']) , ' dragNdrop' action: #toggleDragNDrop.! !!AlignmentMorph methodsFor: 'private' stamp: 'sw 5/6/2000 03:09'!drawSubmorphsOn: aCanvas ((self hasProperty: #clipToOwnerWidth) and: [owner isWorldOrHandMorph not]) ifFalse: [super drawSubmorphsOn: aCanvas] ifTrue: [aCanvas clipBy: (self bounds intersect: owner bounds) during: [:clippedCanvas | super drawSubmorphsOn: clippedCanvas]]! !!AlignmentMorph methodsFor: 'private' stamp: 'jm 11/10/1998 13:14'!extraSpacePerMorph | spaceFillingMorphs spaceNeeded extra | spaceFillingMorphs _ 0. spaceNeeded _ 2 * (inset + borderWidth). orientation = #horizontal ifTrue: [ submorphs do: [:m | spaceNeeded _ spaceNeeded + (m minWidth max: minCellSize). (m isAlignmentMorph and: [m hResizing = #spaceFill]) ifTrue: [spaceFillingMorphs _ spaceFillingMorphs + 1]]. extra _ (bounds width - spaceNeeded) max: 0. ] ifFalse: [ submorphs do: [:m | spaceNeeded _ spaceNeeded + (m minHeight max: minCellSize). (m isAlignmentMorph and: [m vResizing = #spaceFill]) ifTrue: [spaceFillingMorphs _ spaceFillingMorphs + 1]]. extra _ (bounds height - spaceNeeded) max: 0]. (submorphs size <= 1 or: [spaceFillingMorphs <= 1]) ifTrue: [^ extra]. ^ extra asFloat / spaceFillingMorphs! !!AlignmentMorph methodsFor: 'private' stamp: 'jm 11/10/1998 13:33'!fixLayout | extraPerMorph fractionalExtra fractionAccumulator nextPlace extra space | extraPerMorph _ self extraSpacePerMorph asFloat. fractionalExtra _ extraPerMorph fractionPart. extraPerMorph _ extraPerMorph truncated. orientation = #horizontal ifTrue: [nextPlace _ bounds left + inset + borderWidth] ifFalse: [nextPlace _ bounds top + inset + borderWidth]. fractionAccumulator _ 0.0. submorphs do: [:m | fractionAccumulator _ fractionAccumulator + fractionalExtra. fractionAccumulator > 0.5 ifTrue: [ extra _ extraPerMorph + 1. fractionAccumulator _ fractionAccumulator - 1.0] ifFalse: [extra _ extraPerMorph]. space _ self placeAndSize: m at: nextPlace padding: extra. nextPlace _ nextPlace + space].! !!AlignmentMorph methodsFor: 'private' stamp: 'di 11/26/1999 22:11'!layoutInWidth: w height: h "Adjust the size of the receiver in its space-filling dimensions during layout. This message is sent to only to layout submorphs." ((hResizing = #spaceFill) and: [bounds width ~= w]) ifTrue: [ bounds _ bounds origin extent: (w @ bounds height). self layoutChanged]. ((vResizing = #spaceFill) and: [bounds height ~= h]) ifTrue: [ bounds _ bounds origin extent: (bounds width @ h). self layoutChanged].! !!AlignmentMorph methodsFor: 'private' stamp: 'sw 5/6/2000 02:53'!resizeIfNeeded "Resize this morph if it is space-filling or shrink-wrap and its owner is not a layout morph." | newWidth newHeight | newWidth _ bounds width. newHeight _ bounds height. (owner == nil or: [owner isAlignmentMorph not]) ifTrue: "if spaceFill and not in a LayoutMorph, grow to enclose submorphs" [hResizing = #spaceFill ifTrue: [newWidth _ self minWidth max: self bounds width. owner ifNotNil: [(self hasProperty: #clipToOwnerWidth) ifTrue: [newWidth _ newWidth min: (owner right - bounds left)]]]. vResizing = #spaceFill ifTrue: [newHeight _ self minHeight max: self bounds height]]. "if shrinkWrap, adjust size to just fit around submorphs" hResizing = #shrinkWrap ifTrue: [newWidth _ self minWidth]. vResizing = #shrinkWrap ifTrue: [newHeight _ self minHeight]. ((newWidth ~= bounds width) or: [newHeight ~= bounds height]) ifTrue: ["bounds really changed" bounds _ bounds origin extent: newWidth@newHeight].! !!AlignmentMorph methodsFor: 'object fileIn' stamp: 'tk 1/3/2000 16:07'!convertbosfcebbochvimol0: varDict bosfcebbochvimolp0: smartRefStrm "These variables are automatically stored into the new instance ('orientation' 'centering' 'hResizing' 'vResizing' 'inset' 'minCellSize' 'openToDragNDrop' 'layoutNeeded' ). This method is for additional changes. Use statements like (foo _ varDict at: 'foo')." "New variables: ('priorFullBounds' ) If a non-nil value is needed, please assign it."! !!AlignmentMorph methodsFor: 'object fileIn' stamp: 'mir 5/18/2000 15:21'!convertbosfcebbochvimolp0: varDict bosfcebbochvimlp0: smartRefStrm "These variables are automatically stored into the new instance ('bounds' 'owner' 'submorphs' 'fullBounds' 'color' 'extension' 'borderWidth' 'borderColor' 'orientation' 'centering' 'hResizing' 'vResizing' 'inset' 'minCellSize' 'layoutNeeded' 'priorFullBounds' ). This method is for additional changes. Use statements like (foo _ varDict at: 'foo')." "These are going away ('openToDragNDrop' ). Possibly store their info in another variable?" self enableDragNDrop: (varDict at: 'openToDragNDrop')! !!AlignmentMorph class methodsFor: 'instance creation' stamp: 'sw 3/2/1999 14:46'!newVariableTransparentSpacer "Answer a space-filling instance of me of the given color." ^ self new hResizing: #spaceFill; vResizing: #spaceFill; inset: 0; borderWidth: 0; color: Color transparent! !!AmbientEvent methodsFor: 'as yet unclassified' stamp: 'di 8/3/1998 21:27'!morph ^ morph! !!AmbientEvent methodsFor: 'as yet unclassified' stamp: 'di 8/3/1998 20:09'!morph: m morph _ m! !!AmbientEvent methodsFor: 'as yet unclassified' stamp: 'di 8/4/1998 15:47'!occurAtTime: ticks inScorePlayer: player atIndex: index inEventTrack: track secsPerTick: secsPerTick (target == nil or: [selector == nil]) ifTrue: [^ morph encounteredAtTime: ticks inScorePlayer: player atIndex: index inEventTrack: track secsPerTick: secsPerTick]. target perform: selector withArguments: arguments! !!AmbientEvent methodsFor: 'as yet unclassified' stamp: 'sw 12/30/1998 19:48'!relatedPlayer (morph isMemberOf: MovieFrameSyncMorph) ifFalse: [^ nil]. ^ morph moviePlayerMorph! !!AmbientEvent methodsFor: 'as yet unclassified' stamp: 'di 8/3/1998 20:08'!target: t selector: s arguments: a target _ t. selector _ s. arguments _ a.! !The Animation class extends the AbstractAnimation class with methods designed for simple (non-composite) animations.!!Animation methodsFor: 'initialization' stamp: 'jsp 3/9/1999 15:48'!object: anObject update: func getStartState: startFunc getEndState: endFunc style: styleFunc duration: time undoable: canUndo inWonderland: aWonderland "This method initializes the Animation with all the information that it needs run." animatedObject _ anObject. updateFunction _ func. styleFunction _ styleFunc. getStartStateFunction _ startFunc. getEndStateFunction _ endFunc. duration _ time. undoable _ canUndo. myScheduler _ aWonderland getScheduler. myWonderland _ aWonderland. loopCount _ 1. direction _ Forward. state _ Waiting. myScheduler addAnimation: self.! !!Animation methodsFor: 'management' stamp: 'jsp 3/3/1999 12:02'!update: currentTime "Updates the animation using the current Wonderland time" | newState | (state = Waiting) ifTrue: [self prologue: currentTime]. (state = Running) ifTrue: [ proportionDone _ styleFunction value: (currentTime - startTime) value: duration. newState _ startState interpolateTo: endState at: proportionDone. updateFunction value: newState. (currentTime >= endTime) ifTrue: [ state _ Finished. ]. ]. (state = Finished) ifTrue: [self epilogue: currentTime].! !I represent a Squeak front-end to Applescript. My instances represent either compiled scripts, contexts or both. My instances maintain separately the original source code from which I was compiled, and then a CompiledApplescript corresponding to that source code in its "current state." I provide facilities for executing my scripts, alone or in various contexts, as well as for recompiling my script to restore the script to its initial state (if the script bears context information).Examples: To execute some text: Applescript doIt: 'beep 3' To compile code into a script object (for MUCH faster execution of repeated tasks, and to maintain state between execution), and then to execute the code: |aVariable| aVariable _ Applescript on: ' property sam: 0 set sam to sam + 1 beep sam'. aVariable doIt Other. somewhat more general operations Applescript doIt: aString mode: anInteger Applescript doIt: aString in: aContext mode: anInteger s _ Applescript on: aString mode: anInteger s doItMode: anInteger s doItIn: aContext s doItIn: aContext mode: anInteger s recompile Also note the examples in the class side of me. !!Applescript methodsFor: 'accessing' stamp: 'acg 9/26/1999 01:00'!compiledScript ^compiledScript! !!Applescript methodsFor: 'accessing' stamp: 'acg 9/27/1999 00:32'!modeDocumentation" 16r0000 kOSAModeNull (kOSANullMode) 16r0001 kOSAModePreventGetSource 16r0002 kOSAModeCompileIntoContext 16r0004 kOSAModeAugmentContext 16r0008 kOSAModeDisplayForHumans kOSAModeNeverInteract kOSAModeCanInteract kOSAModeAlwaysInteract kOSAModeDontReconnect 16r0040 kOSAModeCantSwitchLayer 16r1000 kOSAModeDoRecord 16r4000 kOSAModeDontStoreParent"! !!Applescript methodsFor: 'accessing' stamp: 'acg 9/26/1999 00:59'!source ^source! !!Applescript methodsFor: 'testing' stamp: 'acg 9/26/1999 22:40'!hasSource ^self doAsOSAID: [:o | Applescript generic hasSource: o]! !!Applescript methodsFor: 'testing' stamp: 'acg 9/26/1999 22:39'!isCompiledScript ^self doAsOSAID: [:o | Applescript generic isCompiledScript: o]! !!Applescript methodsFor: 'testing' stamp: 'acg 9/26/1999 22:39'!isScriptContext ^self doAsOSAID: [:o | Applescript generic isScriptContext: o]! !!Applescript methodsFor: 'testing' stamp: 'acg 9/26/1999 22:39'!isScriptValue ^self doAsOSAID: [:o | Applescript generic isScriptValue: o]! !!Applescript methodsFor: 'testing' stamp: 'acg 9/26/1999 22:39'!timesModified ^self doAsOSAID: [:o | Applescript generic timesModified: o]! !!Applescript methodsFor: 'interpreting' stamp: 'acg 9/26/1999 21:13'!asContextDoOSAID: scptOSAID mode: anInteger "Answer a string corresponding to the result of executing preloaded scptOSAID using my compiledScript as the context, and using mode anInteger. As a side-effect, update my script information as necessary. (This routine will not update any stored versions of scptOSAID" ^self doAsOSAID: [:contextOSAID | ApplescriptGeneric executeAndDisplayOSAID: scptOSAID in: contextOSAID mode: anInteger] onErrorDo: [ApplescriptError syntaxErrorFor: (String streamContents: [:aStream | aStream nextPutAll: (ApplescriptGeneric sourceOfOSAID: scptOSAID); cr; cr; nextPutAll: '<=== Source Code of Context ===>'; cr; nextPutAll: source]) withComponent: ApplescriptGeneric]! !!Applescript methodsFor: 'interpreting' stamp: 'acg 9/26/1999 20:43'!doIt "Answer a string corresponding to the result of executing my script in the default context. mode 0. As a side-effect, update my script information as necessary." ^self doAsOSAID: [:scptOSAID | ApplescriptGeneric executeAndDisplayOSAID: scptOSAID in: (OSAID new) mode: 0]! !!Applescript methodsFor: 'interpreting' stamp: 'acg 9/26/1999 21:22'!doItIn: aContext "Answer a string corresponding to the result of executing my script in aContext. mode 0. As a side-effect, update my script and the aContext information as necessary." ^self doAsOSAID: [:scptContext | aContext asContextDoOSAID: scptContext mode: 0]! !!Applescript methodsFor: 'interpreting' stamp: 'acg 9/26/1999 20:43'!doItIn: aContext mode: anInteger "Answer a string corresponding to the result of executing my script in aContext. mode anInteger. As a side-effect, update my script and the aContext information as necessary." ^self doAsOSAID: [:scptContext | aContext asContextDoOSAID: scptContext mode: anInteger]! !!Applescript methodsFor: 'interpreting' stamp: 'acg 9/26/1999 20:43'!doItMode: anInteger "Answer a string corresponding to the result of executing my script in the default context. mode anInteger. As a side-effect, update my script information as necessary." ^self doAsOSAID: [:scptOSAID | ApplescriptGeneric executeAndDisplayOSAID: scptOSAID in: (OSAID new) mode: anInteger]! !!Applescript methodsFor: 'recompiling' stamp: 'acg 9/26/1999 20:55'!recompile self on: source! !!Applescript methodsFor: 'recompiling' stamp: 'acg 9/26/1999 20:55'!recompileMode: anInteger self on: source mode: anInteger! !!Applescript methodsFor: 'printing' stamp: 'acg 9/26/1999 22:52'!printOn: aStream aStream nextPutAll: 'an Applescript('. self isCompiledScript ifTrue: [aStream nextPutAll: 'script ']. self isScriptContext ifTrue: [aStream nextPutAll: 'context ']. aStream nextPutAll: compiledScript size asString; nextPutAll: ' bytes)'! !!Applescript methodsFor: 'private' stamp: 'acg 9/26/1999 20:59'!doAsOSAID: aBlock "Answer the result of performing aBlock on my compiledScript, converted to OSAID form. As a side-effect, update compiledScript to conform to any changes that may have occurred inside the Applescript scripting component." ^self doAsOSAID: aBlock onErrorDo: [ApplescriptError syntaxErrorFor: source withComponent: ApplescriptGeneric]! !!Applescript methodsFor: 'private' stamp: 'acg 9/27/1999 00:04'!doAsOSAID: aCodeBlock onErrorDo: anErrorBlock "Answer the result of performing aBlock on my compiledScript, converted to OSAID form. As a side-effect, update compiledScript to conform to any changes that may have occurred inside the Applescript scripting component." | anOSAID result | anOSAID _ compiledScript asAEDesc asOSAIDThenDisposeAEDescWith: ApplescriptGeneric. result _ aCodeBlock value: anOSAID. compiledScript _ (anOSAID asCompiledApplescriptWith: ApplescriptGeneric) ifNil: [compiledScript]. anOSAID disposeWith: ApplescriptGeneric. ^result ifNil: [anErrorBlock value]! !!Applescript methodsFor: 'private' stamp: 'acg 9/26/1999 21:00'!on: aString ^self on: aString mode: 2 onErrorDo: [ApplescriptError syntaxErrorFor: aString withComponent: ApplescriptGeneric]! !!Applescript methodsFor: 'private' stamp: 'acg 9/26/1999 20:59'!on: aString mode: anInteger ^self on: aString mode: anInteger onErrorDo: [ApplescriptError syntaxErrorFor: aString withComponent: ApplescriptGeneric]! !!Applescript methodsFor: 'private' stamp: 'acg 9/26/1999 20:47'!on: aString mode: anInteger onErrorDo: aBlock source _ aString. compiledScript _ ApplescriptGeneric compile: aString mode: anInteger. compiledScript ifNil: [^aBlock value]. ^self! !!Applescript class methodsFor: 'instance creation' stamp: 'acg 9/25/1999 23:36'!on: aString ^super new on: aString! !!Applescript class methodsFor: 'instance creation' stamp: 'acg 9/26/1999 20:49'!on: aString mode: anInteger ^super new on: aString mode: anInteger! !!Applescript class methodsFor: 'generic scripting component' stamp: 'acg 9/26/1999 02:19'!doIt: aString ^(self on: aString) doIt! !!Applescript class methodsFor: 'generic scripting component' stamp: 'acg 9/26/1999 20:50'!doIt: aString in: aContext mode: anInteger ^(self on: aString mode: anInteger) doItIn: aContext mode: anInteger! !!Applescript class methodsFor: 'generic scripting component' stamp: 'acg 9/26/1999 20:50'!doIt: aString mode: anInteger ^(self on: aString mode: anInteger) doItMode: anInteger! !!Applescript class methodsFor: 'generic scripting component' stamp: 'acg 9/25/1999 23:43'!generic "Answer an ApplescriptInstance (Applescript Generic Scripting Component) that is guaranteed to be active from startUp, but is not (at present) guaranteed to be identical across startups. Additional instances can be created for multi-threaded applications by using ApplescriptInstance." ^ApplescriptGeneric ifNil: [ApplescriptGeneric _ ApplescriptInstance new]! !!Applescript class methodsFor: 'generic scripting component' stamp: 'acg 9/25/1999 23:28'!lastError ^self generic lastError! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!beep: anInteger "Beep n times" ^self doIt: 'beep ', anInteger asString! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!browse: anUrl "Open Microsoft's Web Browser to a page" ^self doIt: 'tell application "Internet Explorer" activate openURL "', anUrl, '" end tell'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!distill Applescript doIt: 'set prompt to "Select a file to convert to .pdf format"set myFile to (choose file with prompt prompt of type "TEXT")tell application "Acrobat™ Distiller™ 3.02" activate open myFileend tell'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!mandatoryDemo "A mandatory first script" ^self doIt: '3 + 4'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/27/1999 08:12'!playQT4Movie "Demonstrate Access to Quicktime" ^Applescript doIt: '-- Play QuickTime File-- ©1999 Sal Soghoian, Apple Computerproperty source_folder : ""property container_kind : "folder"property reset_string : "Pick New Source Folder"-- Check the version of QuickTimecopy my gestaltVersion_info("qtim", 8) to {QT_version, QT_string}if the QT_version is less than "0400" then display dialog "This script requires QuickTime 4.0 or higher." & ¬ return & return & "The currently installed version is: " & ¬ QT_string buttons {"Cancel"} default button 1end if-- Check the version of the OScopy my gestaltVersion_info("sysv", 4) to {system_version, system_string}if the system_version is less than "0850" then display dialog "This script requires Mac OS 8.5 or higher." & ¬ return & return & "The currently installed version is: " & ¬ system_string buttons {"Cancel"} default button 1end if-- check to see if source folder existstry if the source_folder is "" then error set the source_folder to alias (source_folder as text)on error set the source_folder to choose_source_folder() if the result is false then return "user canceled"end try-- set the target folder to the source folderset the target_folder to the source_folderrepeat -- search the target folder for folders or QT files try tell application "Finder" set the item_list to (the name of every item of ¬ the target_folder whose ¬ (creator type is "TVOD") or ¬ (kind is the container_kind)) as list set the item_list to my ASCII_Sort(item_list) set the beginning of the item_list to "Pick New Source Folder" end tell on error beep display dialog "The chosen folder contains no folders or QuickTime files." buttons {"Show Me", "Cancel"} default button 2 tell application "Finder" activate open the target_folder end tell return "no items" end try -- prompt the user to pick a folder or file set the chosen_item to choose from list the item_list with prompt ¬ "Pick an item:" if the chosen_item is false then return set the chosen_item to the chosen_item as string if the chosen_item is reset_string then set the source_folder to choose_source_folder() if the result is false then return "user canceled" set the target_folder to the source_folder else -- Check the user''s choice to determine whether it''s a file or folder tell application "Finder" if the kind of item chosen_item of the target_folder is the container_kind then -- The user picked a folder. Set the new target folder and repeat the process. set the target_folder to folder chosen_item of the the target_folder else -- The user picked a file. Get the path to the file and exit the repeat. set the chosen_item to (item chosen_item of the target_folder) as alias exit repeat end if end tell end ifend repeat-- Find out if the user wants to play the item in the front or back.set play_in_background to truedisplay dialog "Play the media in the foreground or background?" buttons {"Cancel", "Foreground", "Background"} default button 3if the button returned of the result is "Foreground" then set play_in_background to false-- Quit the QuickTime Player if it is opentell application "Finder" if (the creator type of every process) contains «class TVOD» then ¬ tell application "QuickTime Player" to quitend tell-- Convert the alias to a URL format stringset this_file to "file:///" & my filepath_to_URL(the chosen_item, true, false)-- Tell the QuickTime Player to open the file.-- NOTE: to autoplay, Check the Auto-Play preference in the General setting in the QuickTime Player.tell application "QuickTime Player" if play_in_background is false then activate open location this_fileend tellon gestaltVersion_info(gestalt_code, string_length) try tell application "Finder" to ¬ copy my NumToHex((computer gestalt_code), ¬ string_length) to {a, b, c, d} set the numeric_version to {a, b, c, d} as string if a is "0" then set a to "" set the version_string to (a & b & "." & c & "." & d) as string return {numeric_version, version_string} on error return {"", "unknown"} end tryend gestaltVersion_infoon NumToHex(hexData, stringLength) set hexString to {} repeat with i from stringLength to 1 by -1 set hexString to ((hexData mod 16) as string) & hexString set hexData to hexData div 16 end repeat return (hexString as string)end NumToHexon choose_source_folder() try set the source_folder to choose folder with prompt ¬ "Pick a folder containing Quicktime content:" return the source_folder on error return false end tryend choose_source_folder-- this sub-routine converts a filepath to an encoded URL-- My Disk:My Folder:My File-- My%20Disk/My%20Folder/My%20Fileon filepath_to_URL(this_file, encode_URL_A, encode_URL_B) set this_file to this_file as text set AppleScript''s text item delimiters to ":" set the path_segments to every text item of this_file repeat with i from 1 to the count of the path_segments set this_segment to item i of the path_segments set item i of the path_segments to ¬ my encode_text(this_segment, encode_URL_A, encode_URL_B) end repeat set AppleScript''s text item delimiters to "/" set this_file to the path_segments as string set AppleScript''s text item delimiters to "" return this_fileend filepath_to_URL-- this sub-routine is used to encode texton encode_text(this_text, encode_URL_A, encode_URL_B) set the standard_characters to ¬ "abcdefghijklmnopqrstuvwxyz0123456789" set the URL_A_chars to "$+!!''/?;&@=#%><{}[]\"~`^\\|*" set the URL_B_chars to ".-_:" set the acceptable_characters to the standard_characters if encode_URL_A is false then ¬ set the acceptable_characters to ¬ the acceptable_characters & the URL_A_chars if encode_URL_B is false then ¬ set the acceptable_characters to ¬ the acceptable_characters & the URL_B_chars set the encoded_text to "" repeat with this_char in this_text if this_char is in the acceptable_characters then set the encoded_text to ¬ (the encoded_text & this_char) else set the encoded_text to ¬ (the encoded_text & encode_char(this_char)) as string end if end repeat return the encoded_textend encode_text-- this sub-routine is used to encode a characteron encode_char(this_char) set the ASCII_num to (the ASCII number this_char) set the hex_list to ¬ {"0", "1", "2", "3", "4", "5", "6", "7", "8", ¬ "9", "A", "B", "C", "D", "E", "F"} set x to item ((ASCII_num div 16) + 1) of the hex_list set y to item ((ASCII_num mod 16) + 1) of the hex_list return ("%" & x & y) as stringend encode_char-- This routine sorts a list of strings passed to iton ASCII_Sort(my_list) set the index_list to {} set the sorted_list to {} repeat (the number of items in my_list) times set the low_item to "" repeat with i from 1 to (number of items in my_list) if i is not in the index_list then set this_item to item i of my_list as text if the low_item is "" then set the low_item to this_item set the low_item_index to i else if this_item comes before the low_item then set the low_item to this_item set the low_item_index to i end if end if end repeat set the end of sorted_list to the low_item set the end of the index_list to the low_item_index end repeat return the sorted_listend ASCII_Sort'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!say: aString "Speak the string" ^self doIt: 'say "', aString, '"'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!selectFile "Harness Apple's select file dialog for Squeak" ^self doIt: '(choose file with prompt "Hi guys!!" of type "TEXT") as string'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:16'!selectFolder "Harness Apple's select Folder dialog for Squeak" ^self doIt: '(choose folder with prompt "Hi guys!!") as string'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/21/1999 21:33'!silly Applescript say: 'please prez a button for me'. Applescript sillyButtons. Applescript say: 'thank you for pressing the button' ! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:17'!sillyButtons "A silly Apple GUI demo" ^self doIt: ' display dialog "The Mouse that Roars!!" ', 'buttons {"One", "Two", "Three"} default button "One"'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:17'!sillyDialog "A silly Apple GUI demo" self doIt: 'display dialog "Enter a number between 1 and 10." default answer ""set userValue to {text returned of result} as realif (userValue < 1) or (userValue > 10) then display dialog "That Value is out of range." buttons {"OK"} default button 1else display dialog "Thanks for playing." buttons {"OK"} default button 1end if'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:17'!sillyList "A silly Apple GUI demo" ^Applescript doIt: 'choose from list {"dogs", "cats", "lions", "pick the mouse!!"}', 'with prompt "hi there"', 'default items {"dogs"}', 'OK button name "DoIt!!"', 'cancel button name "Chicken!!"'! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:17'!sleep ^self doIt: 'tell application "Finder" sleepend tell'"Applescript sleep"! !!Applescript class methodsFor: 'sample scripts' stamp: 'acg 9/26/1999 02:17'!with: voiceString say: contentString "Speak the string" ^self doIt: 'say "', contentString, '" using "', voiceString, '"'! !!Applescript class methodsFor: 'initialize-release' stamp: 'acg 9/27/1999 08:35'!initialize Smalltalk addToStartUpList: self after: nil. ApplescriptGeneric _ nil. Applescript generic! !!Applescript class methodsFor: 'initialize-release' stamp: 'acg 9/25/1999 23:29'!reopen ^self generic reopen! !!Applescript class methodsFor: 'initialize-release' stamp: 'ar 2/1/2000 15:42'!startUp Smalltalk platformName = 'Mac OS' "Can be *really* annoying otherwise" ifTrue:[^self reopen]! !I represent a syntax or execution error report for errors encountered when processing Applescripts. As a StringHolder, the string to be viewed is generally the method code or expression containing the error.!!ApplescriptError methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 02:10'!canDiscardEdits ^true! !!ApplescriptError methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 01:26'!code: codeString errorMessage: errString from: fromInteger to: toInteger contents _ codeString. from _ fromInteger. to _ toInteger. errorMessage _ errString! !!ApplescriptError methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 01:25'!contentsSelection ^from to: to! !!ApplescriptError methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 01:27'!list ^Array with: errorMessage! !!ApplescriptError methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 01:27'!listIndex ^1! !!ApplescriptError methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 22:10'!listMenu: aMenu ^aMenu labels: '' lines: #() selections: #()! !!ApplescriptError class methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 21:00'!buildMVCViewOn: aSyntaxError "Answer an MVC view on the given SyntaxError." | topView aListView aCodeView | topView _ StandardSystemView new model: aSyntaxError; label: 'Applescript Error'; minimumSize: 380@220. aListView _ PluggableListView on: aSyntaxError list: #list selected: #listIndex changeSelected: nil menu: #listMenu:. aListView window: (0@0 extent: 380@20). topView addSubView: aListView. aCodeView _ PluggableTextView on: aSyntaxError text: #contents accept: nil readSelection: #contentsSelection menu: #codePaneMenu:shifted:. aCodeView window: (0@0 extent: 380@200). topView addSubView: aCodeView below: aListView. ^ topView! !!ApplescriptError class methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 21:01'!buildMorphicViewOn: aSyntaxError "Answer an Morphic view on the given SyntaxError." | window | window _ (SystemWindow labelled: 'Applescript Error') model: aSyntaxError. window addMorph: (PluggableListMorph on: aSyntaxError list: #list selected: #listIndex changeSelected: nil menu: #listMenu:) frame: (0@0 corner: 1@0.15). window addMorph: (PluggableTextMorph on: aSyntaxError text: #contents accept: nil readSelection: #contentsSelection menu: #codePaneMenu:shifted:) frame: (0@0.15 corner: 1@1). ^ window openInWorldExtent: 380@220! !!ApplescriptError class methodsFor: 'as yet unclassified' stamp: 'sma 4/30/2000 09:19'!open: aSyntaxError "Answer a standard system view whose model is an instance of me." | topView | <primitive: 19> "Simulation guard" Smalltalk isMorphic ifTrue: [self buildMorphicViewOn: aSyntaxError. Project current spawnNewProcessIfThisIsUI: Processor activeProcess. ^ Processor activeProcess suspend]. topView _ self buildMVCViewOn: aSyntaxError. topView controller openNoTerminateDisplayAt: Display extent // 2. Cursor normal show. Processor activeProcess suspend! !!ApplescriptError class methodsFor: 'as yet unclassified' stamp: 'acg 9/26/1999 01:38'!syntaxErrorFor: aString withComponent: anApplescriptInstance |range | range _ anApplescriptInstance lastErrorCodeRange. self open: (super new code: aString errorMessage: anApplescriptInstance lastErrorString from: range first to: range last)! !I represent an Applescript Scripting Component, derived from the Component Manager. For more information about Scripting Components, see Inside Macintosh: Interapplication Communications, at: http://developer.apple.com/techpubs/mac/IAC/IAC-2.html.Essentially, I represent a record comprising a one-word handle to the scripting component. That handle is passed as a matter of course to almost every important Applescript call. Accordingly, I am also the repository for most of the primitives for the Applescript/Squeak interface.!]style[(195 54 285)f1,f1Rhttp://developer.apple.com/techpubs/mac/IAC/IAC-2.html;,f1!!ApplescriptInstance methodsFor: 'testing' stamp: 'acg 9/26/1999 22:43'!hasSource: anOSAID | result | result _ IntegerArray new: 1. (self primOSAGetScriptInfo: anOSAID type: (DescType of: 'gsrc') to: result) isZero ifFalse: [^nil]. ^(result at: 1) > 0! !!ApplescriptInstance methodsFor: 'testing' stamp: 'acg 9/26/1999 22:43'!isCompiledScript: anOSAID | result | result _ IntegerArray new: 1. (self primOSAGetScriptInfo: anOSAID type: (DescType of: 'cscr') to: result) isZero ifFalse: [^nil]. ^(result at: 1) > 0! !!ApplescriptInstance methodsFor: 'testing' stamp: 'acg 9/26/1999 22:43'!isScriptContext: anOSAID | result | result _ IntegerArray new: 1. (self primOSAGetScriptInfo: anOSAID type: (DescType of: 'cntx') to: result) isZero ifFalse: [^nil]. ^(result at: 1) > 0! !!ApplescriptInstance methodsFor: 'testing' stamp: 'acg 9/26/1999 22:43'!isScriptValue: anOSAID | result | result _ IntegerArray new: 1. (self primOSAGetScriptInfo: anOSAID type: (DescType of: 'valu') to: result) isZero ifFalse: [^nil]. ^(result at: 1) > 0! !!ApplescriptInstance methodsFor: 'testing' stamp: 'acg 9/26/1999 22:42'!timesModified: anOSAID | result | result _ IntegerArray new: 1. (self primOSAGetScriptInfo: anOSAID type: (DescType of: 'modi') to: result) isZero ifFalse: [^nil]. ^result at: 1! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'sma 3/15/2000 21:46'!compile: aString ^ self compile: aString mode: 0! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/27/1999 00:05'!compile: aString mode: anInteger | sourceAEDesc objectOSAID objectAEDesc | sourceAEDesc _ AEDesc textTypeOn: aString. (objectOSAID _ self compileAndDisposeAEDesc: sourceAEDesc mode: anInteger) ifNil: [^nil]. (objectAEDesc _ self storeAndDisposeOSAID: objectOSAID type: 'scpt' mode: anInteger) ifNil: [^nil]. ^objectAEDesc asCompiledApplescriptThenDispose! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/27/1999 00:05'!do: aString "Answer text result of compiling script in null context" ^self doScript: aString in: OSAID new mode: 0! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/25/1999 14:14'!do: aString in: contextOSAID mode: anInteger "Answer text result of executing Applescript aString in context contexOSAID in mode: anInteger" | source object result | source _ AEDesc textTypeOn: aString. object _ AEDesc new. result _ self primOSADoScript: source in: contextOSAID mode: anInteger resultType: (DescType of: 'TEXT') to: object. source dispose. result isZero ifFalse: [^nil]. ^object asStringThenDispose! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/25/1999 14:14'!doCompiledScript: aCompiledApplescriptData in: contextOSAID mode: anInteger "Answer text result of executing Applescript aString in context contexOSAID in mode: anInteger" ^self valueOf: aCompiledApplescriptData in: contextOSAID mode: anInteger! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/25/1999 14:14'!doScript: aString "Answer text result of compiling script in null context" ^self do: aString! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/25/1999 14:15'!doScript: aString in: contextOSAID mode: anInteger "Answer text result of executing Applescript aString in context contexOSAID in mode: anInteger" ^self do: aString in: contextOSAID mode: anInteger! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/27/1999 00:06'!scriptingName"Answer the name of my generic scripting component" |aeDesc result | aeDesc _ AEDesc new. result _ self primOSAScriptingComponentNameTo: aeDesc. result isZero ifFalse: [^nil]. ^aeDesc asStringThenDispose.! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/26/1999 21:08'!sourceOfOSAID: anOSAID | anAEDesc result | anAEDesc _ AEDesc new. result _ self primOSAGetSource: anOSAID type: 'TEXT' to: anAEDesc. anOSAID disposeWith: self. result isZero ifFalse: [^'']. ^anAEDesc asStringThenDispose ! !!ApplescriptInstance methodsFor: 'interpreting' stamp: 'acg 9/25/1999 21:53'!valueOf: aCompiledApplescript in: contextOSAID mode: anInteger "Answer text result of executing Applescript aString in context contexOSAID in mode: anInteger" | sourceAEDesc sourceOSAID objectOSAID objectAEDesc | sourceAEDesc _ AEDesc scptTypeOn: aCompiledApplescript. sourceOSAID _ self loadAndDispose: sourceAEDesc mode: anInteger. sourceOSAID ifNil: [^nil]. objectOSAID _ self executeAndDispose: sourceOSAID in: contextOSAID mode: anInteger. objectOSAID ifNil: [^nil]. objectAEDesc _ self displayAndDispose: objectOSAID as: 'TEXT' mode: anInteger. objectAEDesc ifNil: [^nil]. ^objectAEDesc asStringThenDispose! !!ApplescriptInstance methodsFor: 'error handling' stamp: 'acg 9/25/1999 23:27'!lastBriefErrorString "Answer the brief error message for the last error" | aeDesc | aeDesc _ AEDesc new. Applescript generic primOSAScriptError: (DescType of: 'errb') type: (DescType of: 'TEXT') to: aeDesc. ^aeDesc asStringThenDispose! !!ApplescriptInstance methodsFor: 'error handling' stamp: 'acg 9/24/1999 00:06'!lastError |range| range _ self lastErrorCodeRange. ^String streamContents: [:aStream | aStream nextPutAll: 'Error #'; nextPutAll: self lastErrorNumber asString; nextPutAll: ': '; nextPutAll: self lastErrorString; nextPutAll: ' (code '; nextPutAll: range first asString; nextPutAll: ' to '; nextPutAll: range last asString; nextPutAll: ').']! !!ApplescriptInstance methodsFor: 'error handling' stamp: 'acg 9/25/1999 23:27'!lastErrorCodeRange "Answer the brief error message for the last error" | aeDesc recordDesc data from to | aeDesc _ AEDesc new. recordDesc _ AEDesc new. Applescript generic primOSAScriptError: (DescType of: 'erng') type: (DescType of: 'erng') to: aeDesc. aeDesc primAECoerceDesc: (DescType of: 'reco') to: recordDesc. aeDesc dispose. data _ ByteArray new: 2. recordDesc primAEGetKeyPtr: (DescType of: 'srcs') type: (DescType of: 'shor') actual: (DescType of: 'shor') to: data. from _ data shortAt: 1 bigEndian: true. recordDesc primAEGetKeyPtr: (DescType of: 'srce') type: (DescType of: 'shor') actual: (DescType of: 'shor') to: data. to _ data shortAt: 1 bigEndian: true. recordDesc dispose. ^ (from + 1) to: (to + 1)! !!ApplescriptInstance methodsFor: 'error handling' stamp: 'acg 9/25/1999 23:27'!lastErrorNumber "Answer the error code number of the last error" | aeDesc | aeDesc _ AEDesc new. Applescript generic primOSAScriptError: (DescType of: 'errn') type: (DescType of: 'shor') to: aeDesc. ^aeDesc asShortThenDispose! !!ApplescriptInstance methodsFor: 'error handling' stamp: 'acg 9/25/1999 23:27'!lastErrorString "Answer the error message for the last error" | aeDesc | aeDesc _ AEDesc new. Applescript generic primOSAScriptError: (DescType of: 'errs') type: (DescType of: 'TEXT') to: aeDesc. ^aeDesc asStringThenDispose! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/25/1999 13:55'!compileAndDisposeAEDesc: sourceAEDesc mode: anInteger | objectOSAID result | objectOSAID _ OSAID new. result _ self primOSACompile: sourceAEDesc mode: anInteger to: objectOSAID. sourceAEDesc dispose. result isZero ifFalse: [^nil]. ^objectOSAID! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/26/1999 00:14'!displayAndDisposeOSAID: anOSAID as: aString mode: anInteger | anAEDesc result | anOSAID isEmpty ifTrue: [^AEDesc textTypeOn: '']. anAEDesc _ AEDesc new. result _ self primOSADisplay: anOSAID as: (DescType of: aString) mode: anInteger to: anAEDesc. anOSAID disposeWith: self. result isZero ifFalse: [^nil]. ^anAEDesc! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/26/1999 20:29'!executeAndDisplayOSAID: anOSAID in: contextOSAID mode: anInteger | resultOSAID resultAEDesc | resultOSAID _ (self executeOSAID: anOSAID in: contextOSAID mode: anInteger) ifNil: [^nil]. resultAEDesc _ (self displayAndDisposeOSAID: resultOSAID as: 'TEXT' mode: anInteger) ifNil: [^nil]. ^resultAEDesc asStringThenDispose ! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/25/1999 09:57'!executeAndDisposeOSAID: sourceOSAID in: contextOSAID mode: anInteger | objectOSAID result | objectOSAID _ OSAID new. result _ self primOSAExecute: sourceOSAID in: contextOSAID mode: anInteger to: objectOSAID. sourceOSAID disposeWith: self. result isZero ifFalse: [^nil]. ^objectOSAID! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/26/1999 00:03'!executeOSAID: sourceOSAID in: contextOSAID mode: anInteger | objectOSAID result | objectOSAID _ OSAID new. result _ self primOSAExecute: sourceOSAID in: contextOSAID mode: anInteger to: objectOSAID. result isZero ifFalse: [^nil]. ^objectOSAID! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/25/1999 09:57'!loadAndDisposeAEDesc: anAEDesc mode: anInteger | anOSAID result | anOSAID _ OSAID new. result _ self primOSALoad: anAEDesc mode: anInteger to: anOSAID. anAEDesc dispose. result isZero ifFalse: [^nil]. ^anOSAID! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/26/1999 02:59'!makeContextAndDiposeOSAID: anOSAID | result contextOSAID contextAEDesc | contextOSAID _ OSAID new. result _ self primOSAMakeContext: (AEDesc nullType) parent: anOSAID to: contextOSAID. anOSAID dispose. result isZero ifFalse: [^nil]. contextAEDesc _ self storeAndDisposeOSAID: contextOSAID type: 'scpt' mode: 0. contextAEDesc ifNil: [^nil]. ^ contextAEDesc asCompiledApplescriptThenDispose! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/26/1999 02:49'!makeContextAndDisposeOSAID: anOSAID | result contextAEDesc | contextAEDesc _ AEDesc new. result _ self primOSAMakeContext: (AEDesc nullType) parent: anOSAID to: contextAEDesc. result isZero ifFalse: [^nil]. anOSAID disposeWith: self. ^ contextAEDesc asCompiledApplescriptThenDispose! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/26/1999 02:58'!makeContextOSAID: anOSAID | result contextOSAID contextAEDesc | contextOSAID _ OSAID new. result _ self primOSAMakeContext: (AEDesc nullType) parent: anOSAID to: contextOSAID. result isZero ifFalse: [^nil]. contextAEDesc _ self storeAndDisposeOSAID: contextOSAID type: 'scpt' mode: 0. contextAEDesc ifNil: [^nil]. ^ contextAEDesc asCompiledApplescriptThenDispose! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/25/1999 14:17'!storeAndDisposeOSAID: anOSAID type: aString mode: anInteger | theAEDesc result | theAEDesc _ AEDesc new. result _ self primOSAStore: anOSAID resultType: (DescType of: aString) mode: 0 to: (theAEDesc). anOSAID disposeWith: self. result isZero ifFalse: [^nil]. ^theAEDesc! !!ApplescriptInstance methodsFor: 'intermediate operations' stamp: 'acg 9/25/1999 16:41'!storeOSAID: anOSAID type: aString mode: anInteger | theAEDesc result | theAEDesc _ AEDesc new. result _ self primOSAStore: anOSAID resultType: (DescType of: aString) mode: 0 to: (theAEDesc). result isZero ifFalse: [^nil]. ^theAEDesc! !!ApplescriptInstance methodsFor: 'printing' stamp: 'acg 9/26/1999 00:52'!printOn: aStream aStream nextPutAll: 'an '; nextPutAll: self species asString; nextPutAll: '('; nextPutAll: self scriptingName; nextPutAll: ')'! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 21:23'!initialize super type: 'osa ' subtype: 'scpt'! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/22/1999 03:14'!primOSACompile: anAEDesc mode: anInteger to: anOSAID <primitive: 'primOSACompile' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSACompile:mode:to:' withArguments: {anAEDesc. anInteger. anOSAID}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 20:57'!primOSADisplay: source as: type mode: mode to: result <primitive: 'primOSADisplay' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSADisplay:as:mode:to:' withArguments: {source. type. mode. result}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 20:57'!primOSADispose: anOSAID <primitive: 'primOSADispose' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSADispose:' withArguments: {anOSAID}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 20:57'!primOSADoScript: source in: context mode: mode resultType: type to: result <primitive: 'primOSADoScript' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSADoScript:in:mode:resultType:to:' withArguments: {source. context. mode. type. result}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 20:57'!primOSAExecute: script in: context mode: mode to: result <primitive: 'primOSAExecute' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAExecute:in:mode:to:' withArguments: { script. context. mode. result }! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/26/1999 22:24'!primOSAGetScriptInfo: aScriptID type: aDescType to: resultData <primitive: 'primOSAGetScriptInfo' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAGetScriptInfo:type:to:' withArguments: {aScriptID. aDescType. resultData}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/25/1999 17:27'!primOSAGetSource: aScriptID type: aDescType to: resultData <primitive: 'primOSAGetSource' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAGetSource:type:to:' withArguments: {aScriptID. aDescType. resultData}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/22/1999 03:17'!primOSALoad: anAEDesc mode: anInteger to: anOSAID <primitive: 'primOSALoad' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSALoad:mode:to:' withArguments: {anAEDesc. anInteger. anOSAID}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/25/1999 22:56'!primOSAMakeContext: name parent: parent to: result <primitive: 'primOSAMakeContext' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAMakeContext:parent:to:' withArguments: {name. parent. result}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/23/1999 20:43'!primOSAScriptError: anOSType type: aDescType to: anAEDesc <primitive: 'primOSAScriptError' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAScriptError:type:to:' withArguments: {anOSType. aDescType. anAEDesc}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 20:57'!primOSAScriptingComponentNameTo: anAEDesc <primitive: 'primOSAScriptingComponentName' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAScriptingComponentNameTo:' withArguments: {anAEDesc}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/22/1999 04:22'!primOSAStore: a resultType: b mode: c to: d <primitive: 'primOSAStore' module: 'TestOSAPlugin'> ^TestOSAPlugin doPrimitive: 'primOSAStore:resultType:mode:to:' withArguments: {a. b. c. d}! !!ApplescriptInstance methodsFor: 'private' stamp: 'acg 9/21/1999 21:25'!reopen ^super type: 'osa ' subtype: 'scpt'! !!ApplescriptInstance class methodsFor: 'as yet unclassified' stamp: 'acg 9/21/1999 21:22'!new ^super new initialize! !Arcs are an unusual implementation of splines due to Ted Kaehler. Imagine two lines that meet at a corner. Now imagine two moving points; one moves from the corner to the end on one line, the other moves from the end of the other line in to the corner. Now imagine a series of lines drawn between those moving points at each step along the way (they form a sort of spider web pattern). By connecting segments of the intersecting lines, a smooth curve is achieved that is tangent to both of the original lines. Voila.!I present an ArrayedCollection whose elements are objects.!!Array methodsFor: 'converting' stamp: 'sma 5/12/2000 17:32'!asArray "Answer with the receiver itself." ^ self! !!Array methodsFor: 'converting' stamp: 'di 3/28/1999 10:22'!elementsExchangeIdentityWith: otherArray "This primitive performs a bulk mutation, causing all pointers to the elements of this array to be replaced by pointers to the corresponding elements of otherArray. At the same time, all pointers to the elements of otherArray are replaced by pointers to the corresponding elements of this array. The identityHashes remain with the pointers rather than with the objects so that objects in hashed structures should still be properly indexed after the mutation." <primitive: 128> self primitiveFailed! !!Array methodsFor: 'converting' stamp: 'di 3/28/1999 10:23'!elementsForwardIdentityTo: otherArray "This primitive performs a bulk mutation, causing all pointers to the elements of this array to be replaced by pointers to the corresponding elements of otherArray. The identityHashes remain with the pointers rather than with the objects so that the objects in this array should still be properly indexed in any existing hashed structures after the mutation." <primitive: 72> self primitiveFailed! !!Array methodsFor: 'printing' stamp: 'sma 5/12/2000 14:11'!isLiteral ^ self allSatisfy: [:each | each isLiteral]! !!Array methodsFor: 'printing' stamp: 'sma 6/1/2000 09:39'!printOn: aStream aStream nextPut: $#. self printElementsOn: aStream! !!Array methodsFor: 'private' stamp: 'sma 6/3/2000 21:39'!hasLiteral: literal "Answer true if literal is identical to any literal in this array, even if imbedded in further array structure. This method is only intended for private use by CompiledMethod hasLiteralSymbol:" | lit | 1 to: self size do: [:index | (lit _ self at: index) == literal ifTrue: [^ true]. (lit class == Array and: [lit hasLiteral: literal]) ifTrue: [^ true]]. ^ false! !!Array methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 01:42'!byteEncode:aStream aStream writeArray:self.! !!Array methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 01:55'!storeOnStream:aStream self isLiteral ifTrue: [super storeOnStream:aStream] ifFalse:[aStream writeCollection:self].! !!Array class methodsFor: 'plugin generation' stamp: 'acg 9/17/1999 01:12'!ccg: cg emitLoadFor: aString from: anInteger on: aStream cg emitLoad: aString asIntPtrFrom: anInteger on: aStream! !!Array class methodsFor: 'plugin generation' stamp: 'acg 9/19/1999 13:10'!ccg: cg prolog: aBlock expr: aString index: anInteger ^cg ccgLoad: aBlock expr: aString asIntPtrFrom: anInteger andThen: (cg ccgValBlock: 'isIndexable')! !!Array class methodsFor: 'plugin generation' stamp: 'acg 9/17/1999 01:12'!ccgDeclareCForVar: aSymbolOrString ^'int *', aSymbolOrString! !!Array class methodsFor: 'brace support' stamp: 'di 11/18/1999 22:53'!braceStream: nElements "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." ^ WriteStream basicNew braceArray: (self new: nElements)! !!Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:16'!braceWith: a "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array _ self new: 1. array at: 1 put: a. ^ array! !!Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:15'!braceWith: a with: b "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array _ self new: 2. array at: 1 put: a. array at: 2 put: b. ^ array! !!Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:17'!braceWith: a with: b with: c "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array _ self new: 3. array at: 1 put: a. array at: 2 put: b. array at: 3 put: c. ^ array! !!Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:17'!braceWith: a with: b with: c with: d "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array _ self new: 4. array at: 1 put: a. array at: 2 put: b. array at: 3 put: c. array at: 4 put: d. ^ array! !!Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:16'!braceWithNone "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." ^ self new: 0! !A simple 2D-Array implementation. Neither storing nor sorting (otherwise inherited from ArrayedCollection) will work. Neither comparing nor most accessing mehods inherited from Sequenceable collection will work. Actually, it's a bad idea to inherit this class from collection at all!!!!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:16'!at: x at: y "Answer the element at index x,y." ^ contents at: (self indexX: x y: y)! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:20'!at: x at: y add: value "Add value (using #+) to the existing element at index x,y." | index | index _ self indexX: x y: y. ^ contents at: index put: (contents at: index) + value! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:20'!at: x at: y put: value "Store value at index x,y and answer it." ^ contents at: (self indexX: x y: y) put: value! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:20'!atAllPut: anObject "Put anObject at every one of the receiver's indices." contents atAllPut: anObject! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:22'!extent "Answer the receiver's dimensions as point." ^ self width @ self height! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:21'!height "Answer the receiver's second dimension." ^ contents size // width! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:22'!size ^ contents size! !!Array2D methodsFor: 'accessing' stamp: 'sma 4/22/2000 18:22'!width "Answer the receiver's first dimension." ^ width! !!Array2D methodsFor: 'accessing rows/columns' stamp: 'sma 4/22/2000 18:27'!atCol: x "Answer a whole column." | column | column _ contents class new: self height. 1 to: self height do: [:index | column at: index put: (self at: x at: index)]. ^ column! !!Array2D methodsFor: 'accessing rows/columns' stamp: 'sma 4/22/2000 18:30'!atCol: x put: aCollection "Put in a whole column." aCollection size = self height ifFalse: [self error: 'wrong column size']. aCollection doWithIndex: [:value :y | self at: x at: y put: value]. ^ aCollection! !!Array2D methodsFor: 'accessing rows/columns' stamp: 'sma 4/22/2000 18:27'!atRow: y "Answer a whole row." (y < 1 or: [y > self height]) ifTrue: [self errorSubscriptBounds: y]. ^ contents copyFrom: y - 1 * width + 1 to: y * width! !!Array2D methodsFor: 'accessing rows/columns' stamp: 'sma 4/22/2000 18:30'!atRow: y put: aCollection "Put in a whole row." aCollection size = self width ifFalse: [self error: 'wrong row size']. aCollection doWithIndex: [:value :x | self at: x at: y put: value]. ^ aCollection! !!Array2D methodsFor: 'converting' stamp: 'sma 4/22/2000 18:38'!asArray ^ contents copy! !!Array2D methodsFor: 'copying' stamp: 'sma 4/22/2000 18:37'!copy ^ super copy setContents: contents copy! !!Array2D methodsFor: 'enumeration' stamp: 'sma 4/22/2000 18:14'!do: aBlock "Iterate with X varying most quickly. 6/20/96 tk" contents do: aBlock! !!Array2D methodsFor: 'enumeration' stamp: 'sma 4/22/2000 18:39'!rowAndColumnValuesDo: aBlock 1 to: self width do: [:col | 1 to: self height do: [:row | aBlock value: row value: col value: (self at: row at: col)]]! !!Array2D methodsFor: 'enumeration' stamp: 'sma 4/22/2000 18:39'!rowsAndColumnsDo: aBlock 1 to: self width do: [:col | 1 to: self height do: [:row | aBlock value: row value: col]]! !!Array2D methodsFor: 'private' stamp: 'sma 4/22/2000 18:24'!extent: extent fromArray: anArray "Load receiver up from a 1-D array. X varies most quickly. 6/20/96 tk" extent x * extent y = anArray size ifFalse: [^ self error: 'dimensions don''t match']. width _ extent x. contents _ anArray! !!Array2D methodsFor: 'private' stamp: 'sma 4/22/2000 18:16'!indexX: x y: y (x < 1 or: [x > width]) ifTrue: [self errorSubscriptBounds: x]. ^ y - 1 * width + x! !!Array2D methodsFor: 'private' stamp: 'sma 4/22/2000 18:37'!setContents: aCollection contents _ aCollection! !!Array2D methodsFor: 'private' stamp: 'sma 4/22/2000 18:13'!width: x height: y type: collectionClass "Set the number of elements in the first and second dimension. collectionClass can be Array or String or ByteArray." contents == nil ifFalse: [self error: 'No runtime size change yet']. "later move all the elements to the new sized array" width _ x. contents _ collectionClass new: x * y! !!Array2D class methodsFor: 'instance creation' stamp: 'sma 4/22/2000 18:40'!extent: aPoint ^ self width: aPoint x height: aPoint y! !!Array2D class methodsFor: 'instance creation' stamp: 'sma 4/22/2000 18:11'!new: size self error: 'Use >>self width: x height: y<< instead'! !!Array2D class methodsFor: 'instance creation' stamp: 'sma 4/22/2000 18:10'!width: width height: height ^ self basicNew width: width height: height type: Array! !!Array2D class methodsFor: 'instance creation' stamp: 'sma 4/22/2000 18:10'!width: width height: height type: collectionClass ^ self basicNew width: width height: height type: collectionClass! !I am an abstract collection of elements with a fixed range of integers (from 1 to n>=1) as external keys.!!ArrayedCollection methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:36'!size "Answer how many elements the receiver contains." <primitive: 62> ^ self basicSize! !!ArrayedCollection methodsFor: 'adding' stamp: 'sma 5/12/2000 14:09'!add: newObject self shouldNotImplement! !!ArrayedCollection methodsFor: 'filter streaming' stamp: 'sma 5/12/2000 14:20'!flattenOnStream: aStream aStream writeArrayedCollection: self! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 18:18'!asSortedArray self isSorted ifTrue: [^ self asArray]. ^ super asSortedArray! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 6/1/2000 11:57'!isSorted "Return true if the receiver is sorted by the given criterion. Optimization for isSortedBy: [:a :b | a <= b]." | lastElm elm | self isEmpty ifTrue: [^ true]. lastElm _ self first. 2 to: self size do: [:index | elm _ self at: index. lastElm <= elm ifFalse: [^ false]. lastElm _ elm]. ^ true! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 6/1/2000 11:58'!isSortedBy: aBlock "Return true if the receiver is sorted by the given criterion." | lastElm elm | self isEmpty ifTrue: [^ true]. lastElm _ self first. 2 to: self size do: [:index | elm _ self at: index. (aBlock value: lastElm value: elm) ifFalse: [^ false]. lastElm _ elm]. ^ true! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:28'!mergeFirst: first middle: middle last: last into: dst by: aBlock "Private. Merge the sorted ranges [first..middle] and [middle+1..last] of the receiver into the range [first..last] of dst." | i1 i2 val1 val2 out | i1 _ first. i2 _ middle + 1. val1 _ self at: i1. val2 _ self at: i2. out _ first - 1. "will be pre-incremented" "select 'lower' half of the elements based on comparator" [(i1 <= middle) and: [i2 <= last]] whileTrue: [(aBlock value: val1 value: val2) ifTrue: [dst at: (out _ out + 1) put: val1. val1 _ self at: (i1 _ i1 + 1)] ifFalse: [dst at: (out _ out + 1) put: val2. i2 _ i2 + 1. i2 <= last ifTrue: [val2 _ self at: i2]]]. "copy the remaining elements" i1 <= middle ifTrue: [dst replaceFrom: out + 1 to: last with: self startingAt: i1] ifFalse: [dst replaceFrom: out + 1 to: last with: self startingAt: i2]! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:25'!mergeSortFrom: startIndex to: stopIndex by: aBlock "Sort the given range of indices using the mergesort algorithm. Mergesort is a worst-case O(N log N) sorting algorithm that usually does only half as many comparisons as heapsort or quicksort." "Details: recursively split the range to be sorted into two halves, mergesort each half, then merge the two halves together. An extra copy of the data is used as temporary storage and successive merge phases copy data back and forth between the receiver and this copy. The recursion is set up so that the final merge is performed into the receiver, resulting in the receiver being completely sorted." self size <= 1 ifTrue: [^ self]. "nothing to do" startIndex = stopIndex ifTrue: [^ self]. self assert: [startIndex >= 1 and: [startIndex < stopIndex]]. "bad start index" self assert: [stopIndex <= self size]. "bad stop index" self mergeSortFrom: startIndex to: stopIndex src: self clone dst: self by: aBlock! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:26'!mergeSortFrom: first to: last src: src dst: dst by: aBlock "Private. Split the range to be sorted in half, sort each half, and merge the two half-ranges into dst." | middle | first = last ifTrue: [^ self]. middle _ (first + last) // 2. self mergeSortFrom: first to: middle src: dst dst: src by: aBlock. self mergeSortFrom: middle + 1 to: last src: dst dst: src by: aBlock. src mergeFirst: first middle: middle last: last into: dst by: aBlock! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:22'!sort "Sort this array into ascending order using the '<=' operator." self sort: [:a :b | a <= b]! !!ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:21'!sort: aSortBlock "Sort this array using aSortBlock. The block should take two arguments and return true if the first element should preceed the second one." self mergeSortFrom: 1 to: self size by: aSortBlock! !!ArrayedCollection class methodsFor: 'instance creation' stamp: 'sw 10/24/1998 22:22'!with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject with: sixthObject "Answer a new instance of me, containing only the 6 arguments as elements." | newCollection | newCollection _ self new: 6. newCollection at: 1 put: firstObject. newCollection at: 2 put: secondObject. newCollection at: 3 put: thirdObject. newCollection at: 4 put: fourthObject. newCollection at: 5 put: fifthObject. newCollection at: 6 put: sixthObject. ^ newCollection! !!ArrayedCollection class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 17:37'!withAll: aCollection "Create a new collection containing all the elements from aCollection." ^ (self new: aCollection size) replaceFrom: 1 to: aCollection size with: aCollection! !!ArrayedCollection class methodsFor: 'plugin generation' stamp: 'acg 9/20/1999 10:03'!ccg: cg generateCoerceToOopFrom: aNode on: aStream self instSize > 0 ifTrue: [self error: 'cannot auto-coerce arrays with named instance variables']. cg generateCoerceToObjectFromPtr: aNode on: aStream! !!ArrayedCollection class methodsFor: 'plugin generation' stamp: 'acg 10/5/1999 06:18'!ccg: cg generateCoerceToValueFrom: aNode on: aStream cg generateCoerceToPtr: (self ccgDeclareCForVar: '') fromObject: aNode on: aStream! !!AssignmentNode methodsFor: 'initialize-release' stamp: 'di 3/22/1999 12:00'!variable: aVariable value: expression from: encoder (aVariable isMemberOf: MessageAsTempNode) ifTrue: ["Case of remote temp vars" ^ aVariable store: expression from: encoder]. variable _ aVariable. value _ expression! !!AssignmentTileMorph methodsFor: 'initialization' stamp: 'sw 1/17/1999 21:10'!computeOperatorOrExpression | aSuffix | operatorOrExpression _ (assignmentRoot, assignmentSuffix) asSymbol. aSuffix _ ScriptingSystem wordingForAssignmentSuffix: assignmentSuffix. operatorReadoutString _ assignmentRoot, ' ', aSuffix. self line1: operatorReadoutString. self addArrowsIfAppropriate! !!AssignmentTileMorph methodsFor: 'initialization' stamp: 'sw 1/17/1999 21:10'!setAssignmentSuffix: aString assignmentSuffix _ aString. self computeOperatorOrExpression. type _ #operator. self line1: (ScriptingSystem wordingForOperator: operatorOrExpression). self addArrowsIfAppropriate; updateLiteralLabel! !!AssignmentTileMorph methodsFor: 'arrow' stamp: 'sw 11/22/1999 11:14'!addArrowsIfAppropriate "If the receiver's slot is of an appropriate type, add arrows to the tile" (#(number sound boolean menu) includes: dataType) ifTrue: [self addArrows]! !!AssignmentTileMorph methodsFor: 'code generation' stamp: 'sw 12/24/1998 12:33'!storeCodeOn: aStream indent: tabCount aStream nextPutAll: ' assign', (assignmentSuffix copyWithout: $:), 'Getter: #'. aStream nextPutAll: (ScriptingSystem getterSelectorFor: assignmentRoot). aStream nextPutAll: ' setter: #'. aStream nextPutAll: (ScriptingSystem setterSelectorFor: assignmentRoot). aStream nextPutAll: ' amt: '.! !I represent a pair of associated objects--a key and a value. My instances can serve as entries in a dictionary.!!Association methodsFor: 'printing' stamp: 'MPW 1/4/1901 08:31'!propertyListOn: aStream aStream write:key; print:'='; write:value.! !!Association methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 20:53'!byteEncode: aStream aStream writeAssocation:self.! !An asynchronous file allows simple file read and write operations to be performed in parallel with other processing. This is useful in multimedia applications that need to stream large amounts of sound or image data from or to a file while doing other work.!!AsyncFile methodsFor: 'primitives' stamp: 'jm 6/25/1998 07:42'!primClose: fHandle "Close this file. Do nothing if primitive fails." <primitive: 540>! !!AsyncFile methodsFor: 'primitives' stamp: 'jm 6/25/1998 07:54'!primOpen: fileName forWrite: openForWrite semaIndex: semaIndex "Open a file of the given name, and return a handle for that file. Answer the receiver if the primitive succeeds, nil otherwise." <primitive: 541> ^ nil! !!AsyncFile methodsFor: 'primitives' stamp: 'jm 6/25/1998 07:28'!primReadResult: fHandle intoBuffer: buffer at: startIndex count: count "Copy the result of the last read operation into the given buffer starting at the given index. The buffer may be any sort of bytes or words object, excluding CompiledMethods. Answer the number of bytes read. A negative result means: -1 the last operation is still in progress -2 the last operation encountered an error" <primitive: 542> self primitiveFailed! !!AsyncFile methodsFor: 'primitives' stamp: 'di 6/6/2000 14:40'!primReadStart: fHandle fPosition: fPosition count: count "Start a read operation of count bytes starting at the given offset in the given file." <primitive: 543> self error: 'READ THE COMMENT FOR THIS METHOD.'"NOTE: This method will fail if there is insufficient C heap to allocate an internal buffer of the required size (the value of count). If you are trying to read a movie file, then the buffer size will be height*width*2 bytes. Each Squeak image retains a value to be used for this allocation, and it it initially set to 0. If you are wish to play a 640x480 movie, you need room for a buffer of 640*480*2 = 614400 bytes. You should execute the following... Smalltalk extraVMMemory: 800000.Then save-and-quit, restart, and try to open the movie file again. If you are using Async files in another way, find out the value of count when this failure occurs (call it NNNN), and instead of the above, execute... Smalltalk extraVMMemory: Smalltalk extraVMMemory + NNNNthen save-and-quit, restart, and try again."! !!AsyncFile methodsFor: 'primitives' stamp: 'jm 6/25/1998 07:27'!primWriteResult: fHandle "Answer the number of bytes written. A negative result means: -1 the last operation is still in progress -2 the last operation encountered an error" <primitive: 544> self primitiveFailed! !!AsyncFile methodsFor: 'primitives' stamp: 'jm 6/25/1998 08:35'!primWriteStart: fHandle fPosition: fPosition fromBuffer: buffer at: startIndex count: count "Start a write operation of count bytes starting at the given index in the given buffer. The buffer may be any sort of bytes or words object, excluding CompiledMethods. The contents of the buffer are copied into an internal buffer immediately, so the buffer can be reused after the write operation has been started. Fail if there is insufficient C heap to allocate an internal buffer of the requested size." <primitive: 545> writeable ifFalse: [^ self error: 'attempt to write a file opened read-only']. self primitiveFailed! !!AsyncFile methodsFor: 'as yet unclassified'!close fileHandle ifNil: [^ self]. "already closed" self primClose: fileHandle. Smalltalk unregisterExternalObject: semaphore. semaphore _ nil. fileHandle _ nil.! !!AsyncFile methodsFor: 'as yet unclassified' stamp: 'di 7/6/1998 10:58'!fileHandle ^ fileHandle! !!AsyncFile methodsFor: 'as yet unclassified' stamp: 'jm 6/25/1998 07:54'!open: fullFileName forWrite: aBoolean "Open a file of the given name, and return a handle for that file. Answer the receiver if the primitive succeeds, nil otherwise. If openForWrite is true, then: if there is no existing file with this name, then create one else open the existing file in read-write mode otherwise: if there is an existing file with this name, then open it read-only else answer nil." "Note: if an exisiting file is opened for writing, it is NOT truncated. If truncation is desired, the file should be deleted before being opened as an asynchronous file." "Note: On some platforms (e.g., Mac), a file can only have one writer at a time." | semaIndex | name _ fullFileName. writeable _ aBoolean. semaphore _ Semaphore new. semaIndex _ Smalltalk registerExternalObject: semaphore. fileHandle _ self primOpen: name forWrite: writeable semaIndex: semaIndex. fileHandle ifNil: [ Smalltalk unregisterExternalObject: semaphore. semaphore _ nil. ^ nil].! !!AsyncFile methodsFor: 'as yet unclassified' stamp: 'jm 6/25/1998 08:28'!readByteCount: byteCount fromFilePosition: fPosition onCompletionDo: aBlock "Start a read operation to read byteCount's from the given position in this file. and fork a process to await its completion. When the operation completes, evaluate the given block. Note that, since the completion block may run asynchronous, the client may need to use a SharedQueue or a semaphore for synchronization." | buffer n | buffer _ String new: byteCount. self primReadStart: fileHandle fPosition: fPosition count: byteCount. "here's the process that awaits the results:" [ [ semaphore wait. n _ self primReadResult: fileHandle intoBuffer: buffer at: 1 count: byteCount. n = Busy. ] whileTrue. "loop while busy in case the semaphore had excess signals" n = Error ifTrue: [^ self error: 'asynchronous read operation failed']. aBlock value: buffer. ] forkAt: Processor userInterruptPriority.! !!AsyncFile methodsFor: 'as yet unclassified' stamp: 'jm 6/25/1998 10:07'!test: byteCount fileName: fileName "AsyncFile new test: 10000 fileName: 'testData'" | buf1 buf2 bytesWritten bytesRead | buf1 _ String new: byteCount withAll: $x. buf2 _ String new: byteCount. self open: fileName forWrite: true. self primWriteStart: fileHandle fPosition: 0 fromBuffer: buf1 at: 1 count: byteCount. semaphore wait. bytesWritten _ self primWriteResult: fileHandle. self close. self open: fileName forWrite: false. self primReadStart: fileHandle fPosition: 0 count: byteCount. semaphore wait. bytesRead _ self primReadResult: fileHandle intoBuffer: buf2 at: 1 count: byteCount. self close. buf1 = buf2 ifFalse: [self error: 'buffers do not match']. ^ 'wrote ', bytesWritten printString, ' bytes; ', 'read ', bytesRead printString, ' bytes'! !!AsyncFile methodsFor: 'as yet unclassified' stamp: 'di 7/6/1998 10:58'!waitForCompletion semaphore wait! !!AsyncFile methodsFor: 'as yet unclassified' stamp: 'jm 6/25/1998 17:28'!writeBuffer: buffer atFilePosition: fPosition onCompletionDo: aBlock "Start an operation to write the contents of the buffer at given position in this file, and fork a process to await its completion. When the write completes, evaluate the given block. Note that, since the completion block runs asynchronously, the client may need to use a SharedQueue or a semaphore for synchronization." | n | self primWriteStart: fileHandle fPosition: fPosition fromBuffer: buffer at: 1 count: buffer size. "here's the process that awaits the results:" [ [ semaphore wait. n _ self primWriteResult: fileHandle. n = Busy. ] whileTrue. "loop while busy in case the semaphore had excess signals" n = Error ifTrue: [^ self error: 'asynchronous write operation failed']. n = buffer size ifFalse: [^ self error: 'did not write the entire buffer']. aBlock value. ] forkAt: Processor userInterruptPriority.! !!AsyncFile class methodsFor: 'class initialization' stamp: 'jm 6/25/1998 17:33'!initialize "AsyncFile initialize" "Possible abnormal I/O completion results." Busy _ -1. Error _ -2.! !Implements the asynchronous file primtives!!AsynchFilePlugin methodsFor: 'initialize-release' stamp: 'ar 5/12/2000 16:52'!initialiseModule "Initialise the module" self export: true. ^self cCode: 'asyncFileInit()' inSmalltalk:[true]! !!AsynchFilePlugin methodsFor: 'initialize-release' stamp: 'ar 5/12/2000 16:54'!shutdownModule "Initialise the module" self export: true. ^self cCode: 'asyncFileShutdown()' inSmalltalk:[true]! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'TPR 2/7/2000 13:01'!asyncFileValueOf: oop "Return a pointer to the first byte of the async file record within the given Smalltalk bytes object, or nil if oop is not an async file record." self returnTypeC: 'AsyncFile *'. interpreterProxy success: ((interpreterProxy isIntegerObject: oop) not and: [(interpreterProxy isBytes: oop) and: [(interpreterProxy slotSizeOf: oop) = (self cCode: 'sizeof(AsyncFile)')]]). interpreterProxy failed ifTrue: [^ nil]. ^ self cCode: '(AsyncFile *) (oop + 4)'! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'TPR 3/21/2000 17:08'!primitiveAsyncFileClose: fh | f | self var: #f declareC: 'AsyncFile *f'. self primitive: 'primitiveAsyncFileClose' parameters: #(Oop ). f _ self asyncFileValueOf: fh. self asyncFileClose: f! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'TPR 3/21/2000 17:10'!primitiveAsyncFileOpen: fileName forWrite: writeFlag semaIndex: semaIndex | fileNameSize fOop f | self var: #f declareC: 'AsyncFile *f'. self primitive: 'primitiveAsyncFileOpen' parameters: #(String Boolean SmallInteger ). fileNameSize _ interpreterProxy slotSizeOf: (fileName asOop: String). fOop _ interpreterProxy instantiateClass: interpreterProxy classByteArray indexableSize: (self cCode: 'sizeof(AsyncFile)'). f _ self asyncFileValueOf: fOop. interpreterProxy failed ifFalse: [self cCode: 'asyncFileOpen(f, (int)fileName, fileNameSize, writeFlag, semaIndex)']. ^ fOop! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'JMM 8/10/2000 13:04'!primitiveAsyncFileReadResult: fhandle intoBuffer: buffer at: start count: num | bufferSize bufferPtr r f count startIndex | self var: #f declareC: 'AsyncFile *f'. self primitive: 'primitiveAsyncFileReadResult' parameters: #(Oop Oop SmallInteger SmallInteger ). f _ self asyncFileValueOf: fhandle. count _ num. startIndex _ start. bufferSize _ interpreterProxy slotSizeOf: buffer. "in bytes or words" (interpreterProxy isWords: buffer) ifTrue: ["covert word counts to byte counts" count _ count * 4. startIndex _ startIndex - 1 * 4 + 1. bufferSize _ bufferSize * 4]. interpreterProxy success: (startIndex >= 1 and: [startIndex + count - 1 <= bufferSize]). bufferPtr _ (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: 'int') + startIndex - 1. "adjust for zero-origin indexing" interpreterProxy failed ifFalse: [r _ self cCode: 'asyncFileReadResult(f, bufferPtr, count)']. ^ r asOop: SmallInteger! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'ar 5/13/2000 16:00'!primitiveAsyncFileReadStart: fHandle fPosition: fPosition count: count | f | self var: #f declareC: 'AsyncFile *f'. self primitive: 'primitiveAsyncFileReadStart' parameters: #(Oop SmallInteger SmallInteger). f _ self asyncFileValueOf: fHandle. self cCode: 'asyncFileReadStart(f, fPosition, count)'! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'TPR 2/7/2000 16:09'!primitiveAsyncFileWriteResult: fHandle | f r | self var: #f declareC: 'AsyncFile *f'. self primitive: 'primitiveAsyncFileWriteResult' parameters:#(Oop). f _ self asyncFileValueOf: fHandle. r _ self cCode:' asyncFileWriteResult(f)'. ^r asOop: SmallInteger! !!AsynchFilePlugin methodsFor: 'primitives' stamp: 'JMM 8/10/2000 13:05'!primitiveAsyncFileWriteStart: fHandle fPosition: fPosition fromBuffer: buffer at: start count: num | f bufferSize bufferPtr count startIndex | self var: #f declareC: 'AsyncFile *f'. self primitive: 'primitiveAsyncFileWriteStart' parameters: #(Oop SmallInteger Oop SmallInteger SmallInteger ). f _ self asyncFileValueOf: fHandle. interpreterProxy failed ifTrue: [^ nil]. count _ num. startIndex _ start. bufferSize _ interpreterProxy slotSizeOf: buffer. "in bytes or words" (interpreterProxy isWords: buffer) ifTrue: ["covert word counts to byte counts" count _ count * 4. startIndex _ startIndex - 1 * 4 + 1. bufferSize _ bufferSize * 4]. interpreterProxy success: (startIndex >= 1 and: [startIndex + count - 1 <= bufferSize]). bufferPtr _ (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: 'int') + startIndex - 1. "adjust for zero-origin indexing" interpreterProxy failed ifFalse: [self cCode: 'asyncFileWriteStart(f, fPosition, bufferPtr, count)']! !!AsynchFilePlugin class methodsFor: 'translation' stamp: 'ar 5/11/2000 22:21'!headerFile^'/* Header file for AsynchFile plugin *//* module initialization/shutdown */int asyncFileInit(void);int asyncFileShutdown(void);/*** Experimental Asynchronous File I/O ***/typedef struct { int sessionID; void *state;} AsyncFile;int asyncFileClose(AsyncFile *f);int asyncFileOpen(AsyncFile *f, int fileNamePtr, int fileNameSize, int writeFlag, int semaIndex);int asyncFileRecordSize();int asyncFileReadResult(AsyncFile *f, int bufferPtr, int bufferSize);int asyncFileReadStart(AsyncFile *f, int fPosition, int count);int asyncFileWriteResult(AsyncFile *f);int asyncFileWriteStart(AsyncFile *f, int fPosition, int bufferPtr, int bufferSize);'! !!AtomMorph methodsFor: 'as yet unclassified' stamp: 'jm 8/10/1998 17:40'!bounceIn: aRect "Move this atom one step along its velocity vector and make it bounce if it goes outside the given rectangle. Return true if it is bounced." | p vx vy px py bounced | p _ self position. vx _ velocity x. vy _ velocity y. px _ p x + vx. py _ p y + vy. bounced _ false. px > aRect right ifTrue: [ px _ aRect right - (px - aRect right). vx _ velocity x negated. bounced _ true]. py > aRect bottom ifTrue: [ py _ aRect bottom - (py - aRect bottom). vy _ velocity y negated. bounced _ true]. px < aRect left ifTrue: [ px _ aRect left - (px - aRect left). vx _ velocity x negated. bounced _ true]. py < aRect top ifTrue: [ py _ aRect top - (py - aRect top). vy _ velocity y negated. bounced _ true]. self position: px @ py. bounced ifTrue: [self velocity: vx @ vy]. ^ bounced! !a stream on Text's which keeps track of the last attribute put; new characters are added with those attributes.instance vars: characters - a WriteStream of the characters in the stream attributeRuns - a RunArray with the attributes for the stream currentAttributes - the attributes to be used for new text attributesChanged - whether the attributes have changed since the last addition!!AttributedTextStream methodsFor: 'retrieving the text' stamp: 'ls 6/27/1998 15:04'!contents | ans | ans _ Text new: characters size. ans setString: characters contents setRuns: attributeRuns. "this is declared private, but it's exactly what I need, and it's declared as exactly what I want it to do...." ^ans! !!AttributedTextStream methodsFor: 'stream protocol' stamp: 'ls 6/27/1998 14:59'!nextPut: aChar attributesChanged ifTrue: [ attributeRuns addLast: currentAttributes. attributesChanged _ false ] ifFalse: [ attributeRuns repeatLastIfEmpty: [ OrderedCollection new ] ]. characters nextPut: aChar! !!AttributedTextStream methodsFor: 'stream protocol' stamp: 'ls 6/27/1998 15:02'!nextPutAll: aString "add an entire string with the same attributes" attributesChanged ifTrue: [ attributeRuns addLast: currentAttributes times: aString size. attributesChanged _ false. ] ifFalse: [ attributeRuns repeatLast: aString size ifEmpty: [ OrderedCollection new ] ]. characters nextPutAll: aString.! !!AttributedTextStream methodsFor: 'access' stamp: 'ls 6/27/1998 15:09'!currentAttributes "return the current attributes" ^currentAttributes! !!AttributedTextStream methodsFor: 'access' stamp: 'ls 7/28/1998 02:08'!currentAttributes: newAttributes "set the current attributes" attributesChanged _ currentAttributes ~= newAttributes. currentAttributes _ newAttributes.! !!AttributedTextStream methodsFor: 'access' stamp: 'ls 9/10/1998 03:36'!size "number of characters in the stream so far" ^characters size! !!AttributedTextStream methodsFor: 'private-initialization' stamp: 'ls 6/27/1998 15:08'!initialize characters _ WriteStream on: String new. currentAttributes _ OrderedCollection new. attributesChanged _ true. attributeRuns _ RunArray new. ! !!AttributedTextStream class methodsFor: 'instance creation' stamp: 'ls 6/27/1998 15:07'!new ^super basicNew initialize! !!AuthorizedSwikiAction methodsFor: 'URL processing' stamp: 'tk 9/21/1998 08:23'!authorizer "*** Do not use this method to add or delete users!! The change will not be recorded on the disk!! Instead call mapName:password:to: in this class.***" ^authorizer! !!AuthorizedSwikiAction methodsFor: 'URL processing' stamp: 'tk 7/6/1998 07:31'!checkAuthorization: request ^ authorizer ifNotNil: [authorizer user: request userID].! !!AuthorizedSwikiAction methodsFor: 'URL processing' stamp: 'mjg 8/31/199815:32'!process: request self checkAuthorization: request. ^(super process: request).! !!AuthorizedSwikiAction methodsFor: 'URL processing' stamp: 'tk 9/13/1998 20:45'!processSpecial: request "Let SwikiAction process this with no authorization check." ^(super process: request).! !!AuthorizedSwikiAction methodsFor: 'URL processing' stamp: 'tk 6/22/1998 14:15'!restore: nameOfSwiki "Read all files in the directory 'nameOfSwiki'. Reconstruct the url map." | fName | super restore: nameOfSwiki. fName _ ServerAction serverDirectory, name, (ServerAction pathSeparator), 'authorizer'. (FileDirectory new fileExists: fName) ifTrue: [ authorizer _ (FileStream oldFileNamed: fName) fileInObjectAndCode].! !Allows anyone to read the pages of this Swiki, but only authorized users can edit or change pages. Can have multiple users, each with a different password. Each can modify the whole Swiki area.To restart an existing Authorized Swiki: AuthorizedWriteSwiki new restore: 'SWSecure'.The front page URL is: http://serverMachine:80/SWSecure.1To make a completely new one: | a s | a := Authorizer new. a realm: 'SwikiArea'. a mapName: 'viki' password: 'hard2guess' to: 'viki'. AuthorizedWriteSwiki setUp: 'SWSecure'. s := AuthorizedWriteSwiki new restore: 'SWSecure'. s authorizer: a.!!AuthorizedWriteSwiki methodsFor: 'as yet unclassified' stamp: 'tk 9/13/1998 20:59'!process: request "Only demand authorization of name and password when requesting the edit page, requesting the append page, receiving an edit, or receiving an append." | command coreRef | request fields ifNotNil: ["Are there input fields?" coreRef _ request message size < 2 ifTrue: ['1'] ifFalse: [request message at: 2]. coreRef = 'searchresult' ifFalse: ["Must be text for an edit!!" self checkAuthorization: request]]. request message size > 2 ifTrue: ["SearchResult, All, Versions, or Edit" command _ request message at: 3. command = 'edit' ifTrue: [self checkAuthorization: request]. command = 'insert' ifTrue: [self checkAuthorization: request]]. ^(super processSpecial: request). "all the way up to SwikiAction"! !B3DAcceleratorPlugin translate!!B3DAcceleratorPlugin methodsFor: 'initialize-release' stamp: 'ar 5/26/2000 17:23'!initialiseModule self export: true. ^self b3dxInitialize! !!B3DAcceleratorPlugin methodsFor: 'initialize-release' stamp: 'ar 5/26/2000 17:23'!shutdownModule self export: true. ^self b3dxShutdown! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:54'!primitiveBltFromDisplay | result extent srcOrigin dstOrigin extentX extentY sourceX sourceY destX destY formHandle displayHandle | self export: true. interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. extent _ interpreterProxy stackObjectValue: 0. srcOrigin _ interpreterProxy stackObjectValue: 1. dstOrigin _ interpreterProxy stackObjectValue: 2. formHandle _ interpreterProxy stackIntegerValue: 3. displayHandle _ interpreterProxy stackIntegerValue: 4. interpreterProxy failed ifTrue:[^nil]. ((interpreterProxy isPointers: extent) and:[(interpreterProxy slotSizeOf: extent) = 2]) ifFalse:[^interpreterProxy primitiveFail]. ((interpreterProxy isPointers: srcOrigin) and:[(interpreterProxy slotSizeOf: srcOrigin) = 2]) ifFalse:[^interpreterProxy primitiveFail]. ((interpreterProxy isPointers: dstOrigin) and:[(interpreterProxy slotSizeOf: dstOrigin) = 2]) ifFalse:[^interpreterProxy primitiveFail]. extentX _ interpreterProxy fetchInteger: 0 ofObject: extent. extentY _ interpreterProxy fetchInteger: 1 ofObject: extent. sourceX _ interpreterProxy fetchInteger: 0 ofObject: srcOrigin. sourceY _ interpreterProxy fetchInteger: 1 ofObject: srcOrigin. destX _ interpreterProxy fetchInteger: 0 ofObject: dstOrigin. destY _ interpreterProxy fetchInteger: 1 ofObject: dstOrigin. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxBltFromDisplay(displayHandle, formHandle, destX, destY, sourceX, sourceY, extentX, extentY)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 5. "pop args; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:55'!primitiveBltToDisplay | result extent srcOrigin dstOrigin extentX extentY sourceX sourceY destX destY formHandle displayHandle | self export: true. interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. extent _ interpreterProxy stackObjectValue: 0. srcOrigin _ interpreterProxy stackObjectValue: 1. dstOrigin _ interpreterProxy stackObjectValue: 2. formHandle _ interpreterProxy stackIntegerValue: 3. displayHandle _ interpreterProxy stackIntegerValue: 4. interpreterProxy failed ifTrue:[^nil]. ((interpreterProxy isPointers: extent) and:[(interpreterProxy slotSizeOf: extent) = 2]) ifFalse:[^interpreterProxy primitiveFail]. ((interpreterProxy isPointers: srcOrigin) and:[(interpreterProxy slotSizeOf: srcOrigin) = 2]) ifFalse:[^interpreterProxy primitiveFail]. ((interpreterProxy isPointers: dstOrigin) and:[(interpreterProxy slotSizeOf: dstOrigin) = 2]) ifFalse:[^interpreterProxy primitiveFail]. extentX _ interpreterProxy fetchInteger: 0 ofObject: extent. extentY _ interpreterProxy fetchInteger: 1 ofObject: extent. sourceX _ interpreterProxy fetchInteger: 0 ofObject: srcOrigin. sourceY _ interpreterProxy fetchInteger: 1 ofObject: srcOrigin. destX _ interpreterProxy fetchInteger: 0 ofObject: dstOrigin. destY _ interpreterProxy fetchInteger: 1 ofObject: dstOrigin. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxBltToDisplay(displayHandle, formHandle, destX, destY, sourceX, sourceY, extentX, extentY)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 5. "pop args; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:15'!primitiveCreateDisplaySurface | h w d result | self export: true. interpreterProxy methodArgumentCount = 3 ifFalse:[^interpreterProxy primitiveFail]. h _ interpreterProxy stackIntegerValue: 0. w _ interpreterProxy stackIntegerValue: 1. d _ interpreterProxy stackIntegerValue: 2. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxCreateDisplaySurface(w, h, d)' inSmalltalk:[-1]. result = -1 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pop: 4. "args+rcvr" interpreterProxy pushInteger: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:16'!primitiveDestroyDisplaySurface | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxDestroyDisplaySurface(handle)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. "pop arg; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 21:36'!primitiveDisplayGetColorMasks | handle result masks array | self export: true. self var: #masks declareC:'int masks[4]'. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. array _ interpreterProxy stackObjectValue: 0. handle _ interpreterProxy stackIntegerValue: 1. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy fetchClassOf: array) = interpreterProxy classArray ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: array) = 4 ifFalse:[^interpreterProxy primitiveFail]. result _ self cCode:'b3dxDisplayColorMasks(handle, masks)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. 0 to: 3 do:[:i| interpreterProxy storePointer: i ofObject: array withValue: (interpreterProxy positive32BitIntegerFor: (masks at: i))]. interpreterProxy pop: 2. "pop args return receiver"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:16'!primitiveFillDisplaySurface | h w result y x pv handle | self export: true. interpreterProxy methodArgumentCount = 6 ifFalse:[^interpreterProxy primitiveFail]. h _ interpreterProxy stackIntegerValue: 0. w _ interpreterProxy stackIntegerValue: 1. y _ interpreterProxy stackIntegerValue: 2. x _ interpreterProxy stackIntegerValue: 3. pv _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 4). handle _ interpreterProxy stackIntegerValue: 5. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxFillDisplaySurface(handle, pv, x, y, w, h)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 6. "pop args; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:17'!primitiveFinishDisplaySurface | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxFinishDisplaySurface(handle)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. "pop arg; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:17'!primitiveFlushDisplaySurface | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxFlushDisplaySurface(handle)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. "pop arg; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 21:37'!primitiveSupportsDisplayDepth | result depth | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. depth _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self b3dxSupportsDisplayDepth: depth. interpreterProxy pop: 1. interpreterProxy pushBool: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-textures' stamp: 'ar 5/28/2000 01:17'!primitiveAllocateTexture | h w d result | self export: true. interpreterProxy methodArgumentCount = 3 ifFalse:[^interpreterProxy primitiveFail]. h _ interpreterProxy stackIntegerValue: 0. w _ interpreterProxy stackIntegerValue: 1. d _ interpreterProxy stackIntegerValue: 2. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxAllocateTexture(w, h, d)' inSmalltalk:[-1]. result = -1 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pop: 4. "args+rcvr" interpreterProxy pushInteger: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-textures' stamp: 'ar 5/28/2000 01:18'!primitiveDestroyTexture | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxDestroyTexture(handle)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. "pop arg; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 21:37'!primitiveTextureDepth | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxActualTextureDepth(handle)' inSmalltalk:[-1]. result < 0 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pop: 2. interpreterProxy pushInteger: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 21:37'!primitiveTextureGetColorMasks | handle result masks array | self export: true. self var: #masks declareC:'int masks[4]'. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. array _ interpreterProxy stackObjectValue: 0. handle _ interpreterProxy stackIntegerValue: 1. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy fetchClassOf: array) = interpreterProxy classArray ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: array) = 4 ifFalse:[^interpreterProxy primitiveFail]. result _ self cCode:'b3dxTextureColorMasks(handle, masks)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. 0 to: 3 do:[:i| interpreterProxy storePointer: i ofObject: array withValue: (interpreterProxy positive32BitIntegerFor: (masks at: i))]. interpreterProxy pop: 2. "pop args return receiver"! !!B3DAcceleratorPlugin methodsFor: 'primitives-textures' stamp: 'ar 5/28/2000 01:18'!primitiveTextureHeight | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxActualTextureHeight(handle)' inSmalltalk:[-1]. result < 0 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pop: 2. interpreterProxy pushInteger: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-textures' stamp: 'ar 5/28/2000 01:19'!primitiveTextureWidth | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxActualTextureWidth(handle)' inSmalltalk:[-1]. result < 0 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pop: 2. interpreterProxy pushInteger: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-forms' stamp: 'ar 5/28/2000 01:19'!primitiveAllocateForm | h w d result | self export: true. interpreterProxy methodArgumentCount = 3 ifFalse:[^interpreterProxy primitiveFail]. h _ interpreterProxy stackIntegerValue: 0. w _ interpreterProxy stackIntegerValue: 1. d _ interpreterProxy stackIntegerValue: 2. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxAllocateForm(w, h, d)' inSmalltalk:[-1]. result = -1 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pop: 4. "args+rcvr" interpreterProxy pushInteger: result.! !!B3DAcceleratorPlugin methodsFor: 'primitives-forms' stamp: 'ar 5/28/2000 01:19'!primitiveDestroyForm | handle result | self export: true. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. handle _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxDestroyForm(handle)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. "pop arg; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-forms' stamp: 'ar 5/27/2000 21:38'!primitiveFormGetColorMasks | handle result masks array | self export: true. self var: #masks declareC:'int masks[4]'. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. array _ interpreterProxy stackObjectValue: 0. handle _ interpreterProxy stackIntegerValue: 1. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy fetchClassOf: array) = interpreterProxy classArray ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: array) = 4 ifFalse:[^interpreterProxy primitiveFail]. result _ self cCode:'b3dxFormColorMasks(handle, masks)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. 0 to: 3 do:[:i| interpreterProxy storePointer: i ofObject: array withValue: (interpreterProxy positive32BitIntegerFor: (masks at: i))]. interpreterProxy pop: 2. "pop args return receiver"! !!B3DAcceleratorPlugin methodsFor: 'primitives-rasterizer' stamp: 'ar 5/28/2000 01:19'!primitiveClearDepthBuffer | result | self export: true. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. result _ self cCode:'b3dxClearDepthBuffer()'. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 4. "pop args; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-rasterizer' stamp: 'ar 5/28/2000 01:20'!primitiveProcessVertexBuffer | idxCount vtxCount vtxArray idxArray texHandle primType result | self export: true. self var: #idxArray type: 'int *'. self var: #vtxArray type: 'float *'. interpreterProxy methodArgumentCount = 6 ifFalse:[^interpreterProxy primitiveFail]. idxCount _ interpreterProxy stackIntegerValue: 0. vtxCount _ interpreterProxy stackIntegerValue: 2. texHandle _ interpreterProxy stackIntegerValue: 4. primType _ interpreterProxy stackIntegerValue: 5. interpreterProxy failed ifTrue:[^nil]. vtxArray _ self stackPrimitiveVertexArray: 3 ofSize: vtxCount. idxArray _ self stackPrimitiveIndexArray: 1 ofSize: idxCount validate: true forVertexSize: vtxCount. (vtxArray == nil or:[idxArray == nil or:[primType < 1 or:[primType > PrimTypeMax or:[interpreterProxy failed]]]]) ifTrue:[^interpreterProxy primitiveFail]. result _ self cCode:'b3dxRasterizeVertexBuffer(primType, texHandle, vtxArray, vtxCount, idxArray, idxCount)' inSmalltalk:[false]. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 6. "pop args; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitives-rasterizer' stamp: 'ar 5/26/2000 17:24'!primitiveRasterizerVersion self export: true. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. interpreterProxy pushInteger: 1.! !!B3DAcceleratorPlugin methodsFor: 'primitives-rasterizer' stamp: 'ar 5/28/2000 01:20'!primitiveSetViewport | h w y x result | self export: true. interpreterProxy methodArgumentCount = 4 ifFalse:[^interpreterProxy primitiveFail]. h _ interpreterProxy stackIntegerValue: 0. w _ interpreterProxy stackIntegerValue: 1. y _ interpreterProxy stackIntegerValue: 2. x _ interpreterProxy stackIntegerValue: 3. interpreterProxy failed ifTrue:[^nil]. result _ self cCode:'b3dxSetViewport(x, y, w, h)'. result ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 4. "pop args; return rcvr"! !!B3DAcceleratorPlugin methodsFor: 'primitive support' stamp: 'ar 5/26/2000 12:37'!stackPrimitiveIndexArray: stackIndex ofSize: nItems validate: aBool forVertexSize: maxIndex "Load a primitive index array from the interpreter stack. If aBool is true then check that all the indexes are in the range (1,maxIndex). Return a pointer to the index data if successful, nil otherwise." | oop oopSize idxPtr index | self inline: false. self returnTypeC:'void*'. self var: #idxPtr declareC:'int *idxPtr'. oop _ interpreterProxy stackObjectValue: stackIndex. oop = nil ifTrue:[^nil]. (interpreterProxy isWords: oop) ifFalse:[^nil]. oopSize _ interpreterProxy slotSizeOf: oop. oopSize < nItems ifTrue:[^nil]. idxPtr _ self cCoerce: (interpreterProxy firstIndexableField: oop) to:'int *'. aBool ifTrue:[ 0 to: nItems-1 do:[:i| index _ idxPtr at: i. (index < 0 or:[index > maxIndex]) ifTrue:[^nil]]]. ^idxPtr! !!B3DAcceleratorPlugin methodsFor: 'primitive support' stamp: 'ar 5/26/2000 12:38'!stackPrimitiveVertex: index "Load a primitive vertex from the interpreter stack. Return a pointer to the vertex data if successful, nil otherwise." | oop | self inline: false. self returnTypeC:'void*'. oop _ interpreterProxy stackObjectValue: index. oop = nil ifTrue:[^nil]. ((interpreterProxy isWords: oop) and:[(interpreterProxy slotSizeOf: oop) = PrimVertexSize]) ifTrue:[^interpreterProxy firstIndexableField: oop]. ^nil! !!B3DAcceleratorPlugin methodsFor: 'primitive support' stamp: 'ar 5/26/2000 12:38'!stackPrimitiveVertexArray: index ofSize: nItems "Load a primitive vertex array from the interpreter stack. Return a pointer to the vertex data if successful, nil otherwise." | oop oopSize | self inline: false. self returnTypeC:'void*'. oop _ interpreterProxy stackObjectValue: index. oop = nil ifTrue:[^nil]. (interpreterProxy isWords: oop) ifTrue:[ oopSize _ interpreterProxy slotSizeOf: oop. (oopSize >= nItems * PrimVertexSize and:[oopSize \\ PrimVertexSize = 0]) ifTrue:[^interpreterProxy firstIndexableField: oop]]. ^nil! !!B3DAcceleratorPlugin class methodsFor: 'translation' stamp: 'ar 5/28/2000 01:50'!headerFile^'/* Header file for 3D accelerator plugin *//* module initialization support */int b3dxInitialize(void); /* return true on success, false on error */int b3dxShutdown(void); /* return true on success, false on error *//* Display support primitives */int b3dxCreateDisplaySurface(int w, int h, int d); /* return handle or -1 on error */int b3dxDestroyDisplaySurface(int handle); /* return true on success, false on error */int b3dxDisplayColorMasks(int handle, int masks[4]); /* return true on success, false on error */int b3dxSupportsDisplayDepth(int depth); /* return true or false */int b3dxFlushDisplaySurface(int handle); /* return true on success, false on error */int b3dxFinishDisplaySurface(int handle); /* return true on success, false on error *//* optional accelerated blt primitives */int b3dxFillDisplaySurface(int handle, int pv, int x, int y, int w, int h); /* return true on success, false on error */int b3dxBltToDisplay(int displayHandle, int formHandle, int dstX, int dstY, int srcX, int srcY, int w, int h); /* return true on success, false on error */int b3dxBltFromDisplay(int displayHandle, int formHandle, int dstX, int dstY, int srcX, int srcY, int w, int h); /* return true on success, false on error *//* Texture support primitives */int b3dxAllocateTexture(int w, int h, int d); /* return handle or -1 on error */int b3dxDestroyTexture(int handle); /* return true on success, false on error */int b3dxActualTextureDepth(int handle); /* return depth or <0 on error */int b3dxActualTextureWidth(int handle); /* return width or <0 on error */int b3dxActualTextureHeight(int handle); /* return height or <0 on error */int b3dxTextureColorMasks(int handle, int masks[4]); /* return true on success, false on error *//* Form support primitives */int b3dxAllocateForm(int w, int h, int d); /* return handle or -1 on error */int b3dxDestroyForm(int handle); /* return true on success, false on error */int b3dxFormColorMasks(int handle, int masks[4]); /* return true on success, false on error *//* Rasterizer support primitives */int b3dxSetViewport(int x, int y, int w, int h); /* return true on success, false on error */int b3dxClearDepthBuffer(void); /* return true on success, false on error */int b3dxRasterizeVertexBuffer(int primType, int texHandle, float *vtxArray, int vtxSize, int *idxArray, int idxSize); /* return true on success, false on error */'.! !!B3DAcceleratorPlugin class methodsFor: 'translation' stamp: 'ar 5/26/2000 17:25'!moduleName ^'Squeak3DX'! !!B3DActiveEdgeTable methodsFor: 'initialize' stamp: 'ar 4/4/1999 20:55'!initialize array _ Array new: 100. start _ 0. stop _ 0.! !!B3DActiveEdgeTable methodsFor: 'accessing' stamp: 'ar 4/6/1999 02:21'!at: index ^array at: index! !!B3DActiveEdgeTable methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:48'!first ^array at: 1! !!B3DActiveEdgeTable methodsFor: 'accessing' stamp: 'ar 4/6/1999 23:20'!indexOf: anEdge 1 to: stop do:[:i| (array at: i) = anEdge ifTrue:[^i]]. ^0! !!B3DActiveEdgeTable methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:48'!last ^array at: stop! !!B3DActiveEdgeTable methodsFor: 'accessing' stamp: 'ar 4/3/1999 05:28'!size ^stop! !!B3DActiveEdgeTable methodsFor: 'accessing' stamp: 'ar 4/6/1999 03:51'!xValues ^(array copyFrom: 1 to: stop) collect:[:e| e xValue]! !!B3DActiveEdgeTable methodsFor: 'streaming' stamp: 'ar 4/3/1999 05:28'!atEnd ^start >= stop! !!B3DActiveEdgeTable methodsFor: 'streaming' stamp: 'ar 4/3/1999 05:28'!next "Return the next entry from the AET and advance start" ^array at: (start _ start + 1)! !!B3DActiveEdgeTable methodsFor: 'streaming' stamp: 'ar 4/5/1999 23:24'!peek "Peek the next entry from the AET" ^array at: (start + 1)! !!B3DActiveEdgeTable methodsFor: 'streaming' stamp: 'ar 4/3/1999 05:28'!reset start _ 0.! !!B3DActiveEdgeTable methodsFor: 'merging' stamp: 'ar 4/4/1999 21:52'!mergeEdgesFrom: inputList "Merge all the edges from the given input list in the AET" | srcIndex dstIndex outIndex srcEdge dstEdge | srcIndex _ inputList size. srcIndex = 0 ifTrue:[^self]. dstIndex _ stop. "Make room for adding the stuff" [stop + srcIndex > array size] whileTrue:[self grow]. "Adjust size" stop _ stop + srcIndex. "If the receiver is empty, simply copy the stuff" dstIndex = 0 ifTrue:[ 1 to: srcIndex do:[:i| array at: i put: (inputList at: i)]. ^self]. "Merge inputList by walking backwards through the AET and checking each edge." outIndex _ dstIndex+srcIndex. srcEdge _ inputList at: srcIndex. dstEdge _ array at: dstIndex. [true] whileTrue:[ srcEdge xValue >= dstEdge xValue ifTrue:[ "Insert srcEdge" array at: outIndex put: srcEdge. srcIndex _ srcIndex - 1. srcIndex = 0 ifTrue:[^self]. srcEdge _ inputList at: srcIndex. ] ifFalse:[ "Insert dstEdge" array at: outIndex put: dstEdge. dstIndex _ dstIndex - 1. dstIndex = 0 ifTrue:[ 1 to: srcIndex do:[:i| array at: i put: (inputList at: i)]. ^self]. dstEdge _ array at: dstIndex. ]. outIndex _ outIndex-1. ].! !!B3DActiveEdgeTable methodsFor: 'removing' stamp: 'ar 4/5/1999 03:15'!removeFirst stop _ stop - 1. array replaceFrom: start to: stop with: array startingAt: start+1. start _ start - 1. array at: stop+1 put: nil.! !!B3DActiveEdgeTable methodsFor: 'sorting' stamp: 'ar 4/3/1999 05:27'!resortFirst "Resort the first entry in the active edge table" | edge xValue leftEdge newIndex | start = 1 ifTrue:[^self]. "Nothing to do" "Fetch the edge to test." edge _ array at: start. xValue _ edge xValue. "Fetch the next edge left to it." leftEdge _ array at: start-1. leftEdge xValue <= xValue ifTrue:[^self]. "Okay." "Move the edge left to its correct insertion point." newIndex _ start. [newIndex > 1 and:[(leftEdge _ array at: newIndex-1) xValue > xValue]] whileTrue:[ array at: newIndex put: leftEdge. newIndex _ newIndex - 1]. array at: newIndex put: edge.! !!B3DActiveEdgeTable methodsFor: 'testing' stamp: 'ar 4/4/1999 21:21'!isEmpty ^stop = 0! !!B3DActiveEdgeTable methodsFor: 'enumerating' stamp: 'ar 4/5/1999 02:19'!do: aBlock 1 to: stop do:[:i| aBlock value: (array at: i)].! !!B3DActiveEdgeTable methodsFor: 'private' stamp: 'ar 4/5/1999 02:19'!asArray ^array copyFrom: 1 to: stop! !!B3DActiveEdgeTable methodsFor: 'private' stamp: 'ar 4/3/1999 05:25'!grow | newArray | newArray _ array species new: array size + 100. "Grow linearly" newArray replaceFrom: 1 to: array size with: array startingAt: 1. array _ newArray.! !!B3DActiveEdgeTable class methodsFor: 'instance creation' stamp: 'ar 4/4/1999 04:27'!new ^super new initialize! !!B3DAmbientLight methodsFor: 'shading' stamp: 'ar 2/7/1999 17:16'!computeAttenuationFor: distance ^1.0! !!B3DAmbientLight methodsFor: 'shading' stamp: 'ar 2/7/1999 16:56'!computeDirectionTo: aB3DPrimitiveVertex ^B3DVector3 zero! !!B3DAmbientLight methodsFor: 'shading' stamp: 'ar 2/8/1999 00:33'!shadeVertexBuffer: vb with: aMaterial into: colorArray "Overridden for simplicity and speed" | color | false ifTrue:[^super shadeVertexBuffer: vb with: aMaterial into: colorArray]. self flag: #b3dPrimitive. vb trackAmbientColor ifTrue:[ 1 to: vb vertexCount do:[:i| color _ (vb primitiveB3dColorAt: i) * lightColor ambientPart. colorArray add: color at: i. ]. ] ifFalse:[ color _ aMaterial ambientPart * lightColor ambientPart. colorArray += color. ].! !!B3DAmbientLight methodsFor: 'testing' stamp: 'ar 2/8/1999 00:33'!hasDiffusePart ^false! !!B3DAmbientLight methodsFor: 'testing' stamp: 'ar 2/8/1999 00:33'!hasSpecularPart ^false! !!B3DAmbientLight methodsFor: 'converting' stamp: 'ar 2/15/1999 21:52'!asPrimitiveLight "Convert the receiver into a B3DPrimitiveLight" | primLight | primLight _ B3DPrimitiveLight new. primLight ambientPart: lightColor ambientPart. primLight flags: FlagAmbientPart. ^primLight! !!B3DAmbientLight methodsFor: 'converting' stamp: 'ar 2/8/1999 01:29'!transformedBy: aTransformer ^self! !!B3DBox methodsFor: 'displaying' stamp: 'ar 2/16/1999 17:25'!renderOn: aRenderer "Note: The use of BoxColors is an example for pre-lighting." 1 to: 6 do:[:i| "Enable simple additive computation of box colors. Note: This must be turned on on per-primitive basis." aRenderer trackEmissionColor: true; "Turn on pre-lit colors" normal: (BoxNormals at: i); color: (BoxColors at: i); "Set pre-lit color per polygon" drawPolygonAfter:[ aRenderer texCoords: (vertices at: ((BoxFaceIndexes at: i) at: 1)); vertex: (vertices at: ((BoxFaceIndexes at: i) at: 1)); texCoords: (vertices at: ((BoxFaceIndexes at: i) at: 2)); vertex: (vertices at: ((BoxFaceIndexes at: i) at: 2)); texCoords: (vertices at: ((BoxFaceIndexes at: i) at: 3)); vertex: (vertices at: ((BoxFaceIndexes at: i) at: 3)); texCoords: (vertices at: ((BoxFaceIndexes at: i) at: 4)); vertex: (vertices at: ((BoxFaceIndexes at: i) at: 4)). ]. ].! !!B3DBox methodsFor: 'private'!buildBoxFrom: origin to: corner vertices := Array new: 8. 1 to: 8 do:[:i| vertices at: i put: B3DVector3 new]. (vertices at: 1) x: origin x. (vertices at: 1) y: origin y. (vertices at: 1) z: origin z. (vertices at: 2) x: origin x. (vertices at: 2) y: origin y. (vertices at: 2) z: corner z. (vertices at: 3) x: origin x. (vertices at: 3) y: corner y. (vertices at: 3) z: corner z. (vertices at: 4) x: origin x. (vertices at: 4) y: corner y. (vertices at: 4) z: origin z. (vertices at: 5) x: corner x. (vertices at: 5) y: origin y. (vertices at: 5) z: origin z. (vertices at: 6) x: corner x. (vertices at: 6) y: origin y. (vertices at: 6) z: corner z. (vertices at: 7) x: corner x. (vertices at: 7) y: corner y. (vertices at: 7) z: corner z. (vertices at: 8) x: corner x. (vertices at: 8) y: corner y. (vertices at: 8) z: origin z.! !!B3DBox methodsFor: 'accessing' stamp: 'ar 3/12/2000 21:11'!boundingBox ^Rectangle origin: vertices first corner: (vertices at: 7)! !!B3DBox class methodsFor: 'class initialization' stamp: 'ar 2/4/1999 20:20'!initialize "B3DBox initialize" | nrmls | nrmls := #( (-1.0 0.0 0.0) (0.0 1.0 0.0) (1.0 0.0 0.0) (0.0 -1.0 0.0) (0.0 0.0 1.0) (0.0 0.0 -1.0)) collect:[:spec| B3DVector3 x: spec first y: spec second z: spec third]. BoxNormals := nrmls. "BoxNormals := Array new: 6. 1 to: 6 do:[:i| BoxNormals at: i put: (FloatVector3 new). 1 to: 3 do:[:j| (BoxNormals at: i) at: j put: ((nrmls at: i) at: j)]]." BoxFaceIndexes := #( (1 2 3 4) (4 3 7 8) (8 7 6 5) (5 6 2 1) (6 7 3 2) (8 5 1 4)). BoxColors _ #(red green blue yellow gray cyan) collect:[:s| (Color perform: s) alpha: 0.5].! !!B3DBox class methodsFor: 'instance creation'!from: origin to: corner ^self new buildBoxFrom: origin to: corner! !I represent a simple perspective camera.Instance variables: position <B3DVector3> where the camera is located target <B3DVector3> where the camera is aiming at up <B3DVector3> what is considered to be 'up' on screen perspective <B3DCameraPerspective> the actual camera perspective!!B3DCamera methodsFor: 'accessing'!aspectRatio ^perspective aspectRatio! !!B3DCamera methodsFor: 'accessing'!aspectRatio: aFloat ^perspective aspectRatio: aFloat! !!B3DCamera methodsFor: 'accessing' stamp: 'ar 2/8/1999 16:48'!direction ^target - position! !!B3DCamera methodsFor: 'accessing' stamp: 'ar 2/8/1999 16:48'!direction: aVector target _ position + aVector.! !!B3DCamera methodsFor: 'accessing'!farDistance ^perspective farDistance! !!B3DCamera methodsFor: 'accessing'!farDistance: aFloat ^perspective farDistance: aFloat! !!B3DCamera methodsFor: 'accessing'!fieldOfView ^perspective fieldOfView! !!B3DCamera methodsFor: 'accessing'!fieldOfView: aFloat ^perspective fieldOfView: aFloat! !!B3DCamera methodsFor: 'accessing'!fov ^self fieldOfView! !!B3DCamera methodsFor: 'accessing'!fov: aNumber self fieldOfView: aNumber! !!B3DCamera methodsFor: 'accessing'!nearDistance ^perspective nearDistance! !!B3DCamera methodsFor: 'accessing'!nearDistance: aFloat ^perspective nearDistance: aFloat! !!B3DCamera methodsFor: 'accessing'!perspective ^perspective! !!B3DCamera methodsFor: 'accessing'!perspective: aPerspective perspective _ aPerspective! !!B3DCamera methodsFor: 'accessing'!position ^position! !!B3DCamera methodsFor: 'accessing'!position: aVector position _ aVector! !!B3DCamera methodsFor: 'accessing'!target ^target! !!B3DCamera methodsFor: 'accessing'!target: aVector target _ aVector! !!B3DCamera methodsFor: 'accessing'!up ^up! !!B3DCamera methodsFor: 'accessing'!up: aVector up _ aVector! !!B3DCamera methodsFor: 'initialize' stamp: 'ar 3/19/2000 14:12'!from3DS: aDictionary "Initialize the receiver from a 3DS camera. Note: #near and #far are NOT clipping planes in 3DS!!" self position: (aDictionary at: #position). self target: (aDictionary at: #target). self up: (0@1@0). self flag: #TODO. "Include #roll value for upDirection" self fieldOfView: 2400.0 / (aDictionary at: #focal).! !!B3DCamera methodsFor: 'initialize'!from: positionVector to: targetVector up: upVector position := positionVector. target := targetVector. up := upVector.! !!B3DCamera methodsFor: 'initialize' stamp: 'ar 2/5/1999 21:22'!initialize position := B3DVector3 x: 0.0 y: 0.0 z: 1.0. target := B3DVector3 x: 0.0 y: 0.0 z: 0.0. up := B3DVector3 x: 0.0 y: 1.0 z: 0.0. perspective := B3DCameraPerspective new. self fov: 45.0. self aspectRatio: 1.0. self nearDistance: 0.0001. self farDistance: 10000.0.! !!B3DCamera methodsFor: 'initialize' stamp: 'ti 3/27/2000 17:03'!setClippingPlanesFrom: anObject "Set the clipping planes from the given object" | box center radius avgDist | box _ anObject boundingBox. center _ (box origin + box corner) * 0.5. radius _ (center - box origin) length. avgDist _ (position - center) length. self farDistance: avgDist + radius. avgDist > radius ifTrue:[self nearDistance: ((((center - position) normalized dot: (self direction normalized)) * avgDist - radius) max: 1.0e-31)] ifFalse:[self nearDistance: (self farDistance * 0.00001)].! !!B3DCamera methodsFor: 'initialize' stamp: 'ar 2/15/1999 01:04'!setTargetFrom: anObject "Make the camera point at the given object" | box | box _ anObject boundingBox. self target: (box origin + box corner) * 0.5.! !!B3DCamera methodsFor: 'rendering'!renderOn: aRenderer aRenderer lookFrom: self position to: self target up: self up. aRenderer perspective: self perspective.! !!B3DCamera methodsFor: 'experimental' stamp: 'ar 2/17/1999 05:41'!changeDistanceBy: delta position _ target + (position - target * delta)! !!B3DCamera methodsFor: 'experimental' stamp: 'ar 2/17/1999 16:05'!moveToFit: aScene "Move the camera to fit the given scene. Experimental." | distance center | self setTargetFrom: aScene. center _ (aScene boundingBox origin + aScene boundingBox corner) * 0.5. distance _ (aScene boundingBox origin - center) length * 1.3. distance _ distance / (target - position) length. "self inform:'Distance ', distance printString." self changeDistanceBy: distance.! !!B3DCamera methodsFor: 'experimental' stamp: 'ar 2/15/1999 23:47'!rotateBy: angle "Experimental -- rotate around the current up vector by angle degrees. Center at the target point." position _ (B3DMatrix4x4 rotatedBy: angle around: up centeredAt: target) localPointToGlobal: position.! !!B3DCamera methodsFor: 'converting' stamp: 'ti 3/22/2000 10:46'!asMatrix4x4 | xDir yDir zDir m | "calculate z vector" zDir _ self target - self position. zDir safelyNormalize. "calculate x vector" xDir _ self up cross: zDir. xDir safelyNormalize. "recalc y vector" yDir _ zDir cross: xDir. yDir safelyNormalize. m := B3DMatrix4x4 new. m a11: xDir x; a12: xDir y; a13: xDir z; a14: 0.0; a21: yDir x; a22: yDir y; a23: yDir z; a24: 0.0; a31: zDir x; a32: zDir y; a33: zDir z; a34: 0.0; a41: 0.0; a42: 0.0; a43: 0.0; a44: 1.0. m := m composeWith: (B3DMatrix4x4 identity setTranslation: self position negated). ^m! !!B3DCamera class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 23:37'!from3DS: aDictionary ^self new from3DS: aDictionary! !!B3DCamera class methodsFor: 'instance creation'!new ^super new initialize! !I represent a perspective projection.Instance variables: nearDistance <Float> Near clipping plane distance farDistance <Float> Far clipping plane distance fieldOfView <Float> The field of view covered by the perspective aspectRatio <Float> The aspect ratio to be included !!B3DCameraPerspective methodsFor: 'converting'!asFrustum ^B3DViewingFrustum near: nearDistance far: farDistance fov: fieldOfView aspect: aspectRatio! !!B3DCameraPerspective methodsFor: 'converting'!asMatrix4x4 ^self asFrustum asPerspectiveMatrix! !!B3DCameraPerspective methodsFor: 'accessing'!aspectRatio ^aspectRatio! !!B3DCameraPerspective methodsFor: 'accessing'!aspectRatio: aNumber aspectRatio _ aNumber! !!B3DCameraPerspective methodsFor: 'accessing'!farDistance ^farDistance! !!B3DCameraPerspective methodsFor: 'accessing'!farDistance: aNumber farDistance _ aNumber! !!B3DCameraPerspective methodsFor: 'accessing'!fieldOfView ^fieldOfView! !!B3DCameraPerspective methodsFor: 'accessing'!fieldOfView: aNumber fieldOfView _ aNumber! !!B3DCameraPerspective methodsFor: 'accessing'!nearDistance ^nearDistance! !!B3DCameraPerspective methodsFor: 'accessing'!nearDistance: aNumber nearDistance _ aNumber! !!B3DClipperPlugin methodsFor: 'primitives' stamp: 'ar 4/18/1999 02:58'!b3dClipPolygon "Primitive. Clip the polygon given in the vertexArray using the temporary vertex array which is assumed to have sufficient size." | outMask vtxCount vtxArray tempVtxArray count | self export: true. self inline: false. self var: #vtxArray declareC:'int *vtxArray'. self var: #tempVtxArray declareC:'int *tempVtxArray'. interpreterProxy methodArgumentCount = 4 ifFalse:[^interpreterProxy primitiveFail]. outMask _ interpreterProxy stackIntegerValue: 0. vtxCount _ interpreterProxy stackIntegerValue: 2. vtxArray _ self stackPrimitiveVertexArray: 3 ofSize: vtxCount + 4. tempVtxArray _ self stackPrimitiveVertexArray: 1 ofSize: vtxCount + 4. (vtxArray == nil or:[tempVtxArray == nil or:[interpreterProxy failed]]) ifTrue:[^interpreterProxy primitiveFail]. "Hack pointers for one-based indexes" vtxArray _ vtxArray - PrimVertexSize. tempVtxArray _ tempVtxArray - PrimVertexSize. count _ self clipPolygon: vtxArray count: vtxCount with: tempVtxArray mask: outMask. interpreterProxy pop: 4. interpreterProxy pushInteger: count.! !!B3DClipperPlugin methodsFor: 'primitives' stamp: 'ar 4/16/1999 01:54'!b3dDetermineClipFlags "Primitive. Determine the clipping flags for all vertices." | vtxCount vtxArray result | self export: true. self inline: false. self var: #vtxArray declareC:'void *vtxArray'. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. vtxCount _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. vtxArray _ self stackPrimitiveVertexArray: 1 ofSize: vtxCount. (vtxArray == nil or:[interpreterProxy failed]) ifTrue:[^interpreterProxy primitiveFail]. result _ self determineClipFlags: vtxArray count: vtxCount. interpreterProxy failed ifFalse:[ interpreterProxy pop: 3. interpreterProxy pushInteger: result. ].! !!B3DClipperPlugin methodsFor: 'primitives' stamp: 'ar 4/18/1999 02:59'!b3dPrimitiveNextClippedTriangle "Primitive. Return the next clipped triangle from the vertex buffer and return its index." | idxCount vtxCount firstIndex vtxArray idxArray idx1 idx2 idx3 triMask | self export: true. self inline: false. self var: #idxArray declareC:'int *idxArray'. self var: #vtxArray declareC:'int *vtxArray'. interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. idxCount _ interpreterProxy stackIntegerValue: 0. vtxCount _ interpreterProxy stackIntegerValue: 2. firstIndex _ interpreterProxy stackIntegerValue: 4. interpreterProxy failed ifTrue:[^nil]. vtxArray _ self stackPrimitiveVertexArray: 3 ofSize: vtxCount. idxArray _ self stackPrimitiveIndexArray: 1 ofSize: idxCount validate: true forVertexSize: vtxCount. (vtxArray == nil or:[idxArray == nil or:[interpreterProxy failed]]) ifTrue:[^interpreterProxy primitiveFail]. "Hack idxArray and vtxArray for 1-based indexes" idxArray _ idxArray - 1. vtxArray _ vtxArray - PrimVertexSize. firstIndex to: idxCount by: 3 do:[:i| idx1 _ idxArray at: i. idx2 _ idxArray at: i+1. idx3 _ idxArray at: i+2. (idx1 == 0 or:[idx2 == 0 or:[idx3 == 0]]) ifFalse:[ triMask _ ((vtxArray at: idx1 * PrimVertexSize + PrimVtxClipFlags) bitAnd: ((vtxArray at: idx2 * PrimVertexSize + PrimVtxClipFlags) bitAnd: (vtxArray at: idx3 * PrimVertexSize + PrimVtxClipFlags))). "Check if tri is completely inside" (InAllMask bitAnd: triMask) = InAllMask ifFalse:[ "Tri is not completely inside -> needs clipping." (triMask anyMask: OutAllMask) ifTrue:[ "tri is completely outside. Store all zeros" idxArray at: i put: 0. idxArray at: i+1 put: 0. idxArray at: i+2 put: 0. ] ifFalse:[ "tri must be partially clipped." interpreterProxy pop: 6. "args + rcvr" interpreterProxy pushInteger: i. ^nil ]. ]. ]. ]. "No more entries" interpreterProxy pop: 6. "args + rcvr" interpreterProxy pushInteger: 0.! !!B3DClipperPlugin methodsFor: 'clipping' stamp: 'ar 4/16/1999 06:03'!clipPolygon: vtxArray count: vtxCount with: tempVtxArray mask: outMask | count | self var: #vtxArray declareC:'int *vtxArray'. self var: #tempVtxArray declareC:'int *tempVtxArray'. "Check if the polygon is outside one boundary only. If so, just do this single clipping operation avoiding multiple enumeration." outMask = OutLeftBit ifTrue:[^self clipPolygonLeftFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutRightBit ifTrue:[^self clipPolygonRightFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutTopBit ifTrue:[^self clipPolygonTopFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutBottomBit ifTrue:[^self clipPolygonBottomFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutFrontBit ifTrue:[^self clipPolygonFrontFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutBackBit ifTrue:[^self clipPolygonBackFrom: tempVtxArray to: vtxArray count: vtxCount]. "Just do each of the clipping operations" count _ vtxCount. count _ self clipPolygonLeftFrom: vtxArray to: tempVtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonRightFrom: tempVtxArray to: vtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonTopFrom: vtxArray to: tempVtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonBottomFrom: tempVtxArray to: vtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonFrontFrom: vtxArray to: tempVtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonBackFrom: tempVtxArray to: vtxArray count: count. ^count! !!B3DClipperPlugin methodsFor: 'clipping' stamp: 'ar 4/16/1999 01:57'!determineClipFlags: vtxArray count: count | vtxPtr fullMask w w2 flags x y z | self var: #vtxPtr declareC:'float *vtxPtr'. self var: #vtxArray declareC:'void *vtxArray'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #w declareC:'double w'. self var: #w2 declareC:'double w2'. vtxPtr _ self cCoerce: vtxArray to: 'float *'. fullMask _ InAllMask + OutAllMask. 1 to: count do:[:i| w _ vtxPtr at: PrimVtxRasterPosW. w2 _ 0.0 - w. flags _ 0. x _ vtxPtr at: PrimVtxRasterPosX. x >= w2 ifTrue:[flags _ flags bitOr: InLeftBit] ifFalse:[flags _ flags bitOr: OutLeftBit]. x <= w ifTrue:[flags _ flags bitOr: InRightBit] ifFalse:[flags _ flags bitOr: OutRightBit]. y _ vtxPtr at: PrimVtxRasterPosY. y >= w2 ifTrue:[flags _ flags bitOr: InBottomBit] ifFalse:[flags _ flags bitOr: OutBottomBit]. y <= w ifTrue:[flags _ flags bitOr: InTopBit] ifFalse:[flags _ flags bitOr: OutTopBit]. z _ vtxPtr at: PrimVtxRasterPosZ. z >= w2 ifTrue:[flags _ flags bitOr: InFrontBit] ifFalse:[flags _ flags bitOr: OutFrontBit]. z <= w ifTrue:[flags _ flags bitOr: InBackBit] ifFalse:[flags _ flags bitOr: OutBackBit]. fullMask _ fullMask bitAnd: flags. (self cCoerce: vtxPtr to:'int *') at: PrimVtxClipFlags put: flags. vtxPtr _ vtxPtr + PrimVertexSize. ]. ^fullMask! !!B3DClipperPlugin methodsFor: 'clipping' stamp: 'ar 4/21/1999 01:26'!interpolateFrom: last to: next at: t into: out "Interpolate the primitive vertices last/next at the parameter t" | delta rgbaLast lastValue rgbaNext nextValue newValue x y z w w2 flags | self var: #last declareC:'float *last'. self var: #next declareC:'float *next'. self var: #out declareC:'float *out'. self var: #t declareC: 'double t'. self var: #delta declareC: 'double delta'. self var: #rgbaLast declareC:'unsigned int rgbaLast'. self var: #rgbaNext declareC:'unsigned int rgbaNext'. self var: #lastValue declareC:'unsigned int lastValue'. self var: #nextValue declareC:'unsigned int nextValue'. self var: #newValue declareC:'unsigned int newValue'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #w declareC:'double w'. self var: #w2 declareC:'double w2'. "Interpolate raster position" delta _ (next at: PrimVtxRasterPosX) - (last at: PrimVtxRasterPosX). x _ (last at: PrimVtxRasterPosX) + (delta * t). out at: PrimVtxRasterPosX put: (self cCoerce: x to: 'float'). delta _ (next at: PrimVtxRasterPosY) - (last at: PrimVtxRasterPosY). y _ (last at: PrimVtxRasterPosY) + (delta * t). out at: PrimVtxRasterPosY put: (self cCoerce: y to: 'float'). delta _ (next at: PrimVtxRasterPosZ) - (last at: PrimVtxRasterPosZ). z _ (last at: PrimVtxRasterPosZ) + (delta * t). out at: PrimVtxRasterPosZ put: (self cCoerce: z to: 'float'). delta _ (next at: PrimVtxRasterPosW) - (last at: PrimVtxRasterPosW). w _ (last at: PrimVtxRasterPosW) + (delta * t). out at: PrimVtxRasterPosW put: (self cCoerce: w to: 'float'). "Determine new clipFlags" w2 _ 0.0 - w. flags _ 0. x >= w2 ifTrue:[flags _ flags bitOr: InLeftBit] ifFalse:[flags _ flags bitOr: OutLeftBit]. x <= w ifTrue:[flags _ flags bitOr: InRightBit] ifFalse:[flags _ flags bitOr: OutRightBit]. y >= w2 ifTrue:[flags _ flags bitOr: InBottomBit] ifFalse:[flags _ flags bitOr: OutBottomBit]. y <= w ifTrue:[flags _ flags bitOr: InTopBit] ifFalse:[flags _ flags bitOr: OutTopBit]. z >= w2 ifTrue:[flags _ flags bitOr: InFrontBit] ifFalse:[flags _ flags bitOr: OutFrontBit]. z <= w ifTrue:[flags _ flags bitOr: InBackBit] ifFalse:[flags _ flags bitOr: OutBackBit]. (self cCoerce: out to: 'int *') at: PrimVtxClipFlags put: flags. "Interpolate color" rgbaLast _ (self cCoerce: last to:'unsigned int *') at: PrimVtxColor32. lastValue _ rgbaLast bitAnd: 255. rgbaLast _ rgbaLast >> 8. rgbaNext _ (self cCoerce: next to: 'unsigned int *') at: PrimVtxColor32. nextValue _ rgbaNext bitAnd: 255. rgbaNext _ rgbaNext >> 8. delta _ (self cCoerce: (nextValue - lastValue) to:'int') * t. newValue _ (lastValue + delta) asInteger. lastValue _ rgbaLast bitAnd: 255. rgbaLast _ rgbaLast >> 8. nextValue _ rgbaNext bitAnd: 255. rgbaNext _ rgbaNext >> 8. delta _ (self cCoerce: (nextValue - lastValue) to:'int') * t. newValue _ newValue + ((lastValue + delta) asInteger << 8). lastValue _ rgbaLast bitAnd: 255. rgbaLast _ rgbaLast >> 8. nextValue _ rgbaNext bitAnd: 255. rgbaNext _ rgbaNext >> 8. delta _ (self cCoerce: (nextValue - lastValue) to:'int') * t. newValue _ newValue + ((lastValue + delta) asInteger << 16). lastValue _ rgbaLast bitAnd: 255. nextValue _ rgbaNext bitAnd: 255. delta _ (self cCoerce: (nextValue - lastValue) to:'int') * t. newValue _ newValue + ((lastValue + delta) asInteger << 24). (self cCoerce: out to:'unsigned int*') at: PrimVtxColor32 put: newValue. "Interpolate texture coordinates" delta _ (next at: PrimVtxTexCoordU) - (last at: PrimVtxTexCoordU). out at: PrimVtxTexCoordU put: (self cCoerce: (last at: PrimVtxTexCoordU) + (delta * t) to:'float'). delta _ (next at: PrimVtxTexCoordV) - (last at: PrimVtxTexCoordV). out at: PrimVtxTexCoordV put: (self cCoerce: (last at: PrimVtxTexCoordV) + (delta * t) to:'float').! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/16/1999 01:56'!backClipValueFrom: last to: next self returnTypeC:'double'. ^(((self cCoerce: last to: 'float *') at: PrimVtxRasterPosZ) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosW)) / ( (((self cCoerce: next to:'float *') at: PrimVtxRasterPosW) - ((self cCoerce: last to: 'float *') at: PrimVtxRasterPosW)) - (((self cCoerce: next to:'float *') at: PrimVtxRasterPosZ) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosZ)) ).! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/16/1999 06:43'!bottomClipValueFrom: last to: next self returnTypeC:'double'. ^(0.0 - (((self cCoerce: last to: 'float *') at: PrimVtxRasterPosY) + ((self cCoerce: last to:'float *') at: PrimVtxRasterPosW))) / ( (((self cCoerce: next to:'float *') at: PrimVtxRasterPosW) - ((self cCoerce: last to: 'float *') at: PrimVtxRasterPosW)) + (((self cCoerce: next to:'float *') at: PrimVtxRasterPosY) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosY)) ).! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/17/1999 22:18'!clipPolygonBackFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext | self var: #buf1 declareC:'int *buf1'. self var: #buf2 declareC:'int *buf2'. self var: #last declareC:'int *last'. self var: #next declareC:'int *next'. self var: #t declareC: 'double t'. outIndex _ 0. last _ buf1 + (n * PrimVertexSize). next _ buf1 + PrimVertexSize. inLast _ (last at: PrimVtxClipFlags) anyMask: InBackBit. 1 to: n do:[:i| inNext _ (next at: PrimVtxClipFlags) anyMask: InBackBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self backClipValueFrom: last to: next. outIndex _ outIndex + 1. self interpolateFrom: (self cCoerce: last to:'float *') to: (self cCoerce: next to:'float *') at: t into: (self cCoerce: (buf2 + (outIndex * PrimVertexSize)) to:'float*')]. inNext ifTrue:[ outIndex _ outIndex+1. 0 to: PrimVertexSize-1 do:[:j| buf2 at: (outIndex*PrimVertexSize + j) put: (next at: j)]. ]. last _ next. inLast _ inNext. next _ next + PrimVertexSize. ]. ^outIndex! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/17/1999 22:18'!clipPolygonBottomFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext | self var: #buf1 declareC:'int *buf1'. self var: #buf2 declareC:'int *buf2'. self var: #last declareC:'int *last'. self var: #next declareC:'int *next'. self var: #t declareC: 'double t'. outIndex _ 0. last _ buf1 + (n * PrimVertexSize). next _ buf1 + PrimVertexSize. inLast _ (last at: PrimVtxClipFlags) anyMask: InBottomBit. 1 to: n do:[:i| inNext _ (next at: PrimVtxClipFlags) anyMask: InBottomBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self bottomClipValueFrom: last to: next. outIndex _ outIndex + 1. self interpolateFrom: (self cCoerce: last to:'float *') to: (self cCoerce: next to:'float *') at: t into: (self cCoerce: (buf2 + (outIndex * PrimVertexSize)) to:'float*')]. inNext ifTrue:[ outIndex _ outIndex+1. 0 to: PrimVertexSize-1 do:[:j| buf2 at: (outIndex*PrimVertexSize + j) put: (next at: j)]. ]. last _ next. inLast _ inNext. next _ next + PrimVertexSize. ]. ^outIndex! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/17/1999 22:18'!clipPolygonFrontFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext | self var: #buf1 declareC:'int *buf1'. self var: #buf2 declareC:'int *buf2'. self var: #last declareC:'int *last'. self var: #next declareC:'int *next'. self var: #t declareC: 'double t'. outIndex _ 0. last _ buf1 + (n * PrimVertexSize). next _ buf1 + PrimVertexSize. inLast _ (last at: PrimVtxClipFlags) anyMask: InFrontBit. 1 to: n do:[:i| inNext _ (next at: PrimVtxClipFlags) anyMask: InFrontBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self frontClipValueFrom: last to: next. outIndex _ outIndex + 1. self interpolateFrom: (self cCoerce: last to:'float *') to: (self cCoerce: next to:'float *') at: t into: (self cCoerce: (buf2 + (outIndex * PrimVertexSize)) to:'float*')]. inNext ifTrue:[ outIndex _ outIndex+1. 0 to: PrimVertexSize-1 do:[:j| buf2 at: (outIndex*PrimVertexSize + j) put: (next at: j)]. ]. last _ next. inLast _ inNext. next _ next + PrimVertexSize. ]. ^outIndex! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/17/1999 22:18'!clipPolygonLeftFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext | self var: #buf1 declareC:'int *buf1'. self var: #buf2 declareC:'int *buf2'. self var: #last declareC:'int *last'. self var: #next declareC:'int *next'. self var: #t declareC: 'double t'. outIndex _ 0. last _ buf1 + (n * PrimVertexSize). next _ buf1 + PrimVertexSize. inLast _ (last at: PrimVtxClipFlags) anyMask: InLeftBit. 1 to: n do:[:i| inNext _ (next at: PrimVtxClipFlags) anyMask: InLeftBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self leftClipValueFrom: last to: next. outIndex _ outIndex + 1. self interpolateFrom: (self cCoerce: last to:'float *') to: (self cCoerce: next to:'float *') at: t into: (self cCoerce: (buf2 + (outIndex * PrimVertexSize)) to:'float*')]. inNext ifTrue:[ outIndex _ outIndex+1. 0 to: PrimVertexSize-1 do:[:j| buf2 at: (outIndex*PrimVertexSize + j) put: (next at: j)]. ]. last _ next. inLast _ inNext. next _ next + PrimVertexSize. ]. ^outIndex! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/17/1999 22:18'!clipPolygonRightFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext | self var: #buf1 declareC:'int *buf1'. self var: #buf2 declareC:'int *buf2'. self var: #last declareC:'int *last'. self var: #next declareC:'int *next'. self var: #t declareC: 'double t'. outIndex _ 0. last _ buf1 + (n * PrimVertexSize). next _ buf1 + PrimVertexSize. inLast _ (last at: PrimVtxClipFlags) anyMask: InRightBit. 1 to: n do:[:i| inNext _ (next at: PrimVtxClipFlags) anyMask: InRightBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self rightClipValueFrom: last to: next. outIndex _ outIndex + 1. self interpolateFrom: (self cCoerce: last to:'float *') to: (self cCoerce: next to:'float *') at: t into: (self cCoerce: (buf2 + (outIndex * PrimVertexSize)) to:'float*')]. inNext ifTrue:[ outIndex _ outIndex+1. 0 to: PrimVertexSize-1 do:[:j| buf2 at: (outIndex*PrimVertexSize + j) put: (next at: j)]. ]. last _ next. inLast _ inNext. next _ next + PrimVertexSize. ]. ^outIndex! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/17/1999 22:19'!clipPolygonTopFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext | self var: #buf1 declareC:'int *buf1'. self var: #buf2 declareC:'int *buf2'. self var: #last declareC:'int *last'. self var: #next declareC:'int *next'. self var: #t declareC: 'double t'. outIndex _ 0. last _ buf1 + (n * PrimVertexSize). next _ buf1 + PrimVertexSize. inLast _ (last at: PrimVtxClipFlags) anyMask: InTopBit. 1 to: n do:[:i| inNext _ (next at: PrimVtxClipFlags) anyMask: InTopBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self topClipValueFrom: last to: next. outIndex _ outIndex + 1. self interpolateFrom: (self cCoerce: last to:'float *') to: (self cCoerce: next to:'float *') at: t into: (self cCoerce: (buf2 + (outIndex * PrimVertexSize)) to:'float*')]. inNext ifTrue:[ outIndex _ outIndex+1. 0 to: PrimVertexSize-1 do:[:j| buf2 at: (outIndex*PrimVertexSize + j) put: (next at: j)]. ]. last _ next. inLast _ inNext. next _ next + PrimVertexSize. ]. ^outIndex! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/16/1999 06:43'!frontClipValueFrom: last to: next self returnTypeC:'double'. ^(0.0 - (((self cCoerce: last to: 'float *') at: PrimVtxRasterPosZ) + ((self cCoerce: last to:'float *') at: PrimVtxRasterPosW))) / ( (((self cCoerce: next to:'float *') at: PrimVtxRasterPosW) - ((self cCoerce: last to: 'float *') at: PrimVtxRasterPosW)) + (((self cCoerce: next to:'float *') at: PrimVtxRasterPosZ) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosZ)) ).! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/16/1999 06:43'!leftClipValueFrom: last to: next self returnTypeC:'double'. ^(0.0 - (((self cCoerce: last to: 'float *') at: PrimVtxRasterPosX) + ((self cCoerce: last to:'float *') at: PrimVtxRasterPosW))) / ( (((self cCoerce: next to:'float *') at: PrimVtxRasterPosW) - ((self cCoerce: last to: 'float *') at: PrimVtxRasterPosW)) + (((self cCoerce: next to:'float *') at: PrimVtxRasterPosX) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosX)) ).! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/16/1999 01:56'!rightClipValueFrom: last to: next self returnTypeC:'double'. ^(((self cCoerce: last to: 'float *') at: PrimVtxRasterPosX) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosW)) / ( (((self cCoerce: next to:'float *') at: PrimVtxRasterPosW) - ((self cCoerce: last to: 'float *') at: PrimVtxRasterPosW)) - (((self cCoerce: next to:'float *') at: PrimVtxRasterPosX) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosX)) ).! !!B3DClipperPlugin methodsFor: 'clipping utilities' stamp: 'ar 4/16/1999 01:56'!topClipValueFrom: last to: next self returnTypeC:'double'. ^(((self cCoerce: last to: 'float *') at: PrimVtxRasterPosY) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosW)) / ( (((self cCoerce: next to:'float *') at: PrimVtxRasterPosW) - ((self cCoerce: last to: 'float *') at: PrimVtxRasterPosW)) - (((self cCoerce: next to:'float *') at: PrimVtxRasterPosY) - ((self cCoerce: last to:'float *') at: PrimVtxRasterPosY)) ).! !I represent an RGBA color value in floating point format. I am used during the lighting and shading computations.!!B3DColor4 methodsFor: 'accessing'!alpha ^self floatAt: 4! !!B3DColor4 methodsFor: 'accessing'!alpha: aNumber self floatAt: 4 put: aNumber! !!B3DColor4 methodsFor: 'accessing'!blue ^self floatAt: 3! !!B3DColor4 methodsFor: 'accessing'!blue: aNumber self floatAt: 3 put: aNumber! !!B3DColor4 methodsFor: 'accessing'!green ^self floatAt: 2! !!B3DColor4 methodsFor: 'accessing'!green: aNumber self floatAt: 2 put: aNumber! !!B3DColor4 methodsFor: 'accessing'!red ^self floatAt: 1! !!B3DColor4 methodsFor: 'accessing'!red: aNumber self floatAt: 1 put: aNumber! !!B3DColor4 methodsFor: 'converting' stamp: 'ar 5/4/2000 17:59'!asB3DColor ^self! !!B3DColor4 methodsFor: 'converting'!asColor ^Color r: self red g: self green b: self blue alpha: self alpha! !!B3DColor4 methodsFor: 'converting' stamp: 'ar 2/4/1999 20:21'!pixelValue32 ^self asColor pixelWordForDepth: 32! !!B3DColor4 methodsFor: 'private'!privateLoadFrom: srcObject | color | color _ srcObject asColor. self red: color red. self green: color green. self blue: color blue. self alpha: color alpha.! !!B3DColor4 methodsFor: 'initialize' stamp: 'ar 2/7/1999 16:21'!r: rValue g: gValue b: bValue a: aValue self red: rValue. self green: gValue. self blue: bValue. self alpha: aValue.! !!B3DColor4 methodsFor: 'testing' stamp: 'ar 2/15/1999 22:12'!isZero ^self alpha isZero! !!B3DColor4 methodsFor: 'interpolating' stamp: 'jsp 2/8/1999 19:57'!interpolateTo: end at: amountDone "Return the color vector yielded by interpolating from the state of the object to the specified end state at the specified amount done" | newColor r g b a | r _ self red. g _ self green. b _ self blue. a _ self alpha. newColor _ B3DColor4 new. newColor red: r + (((end red) - r) * amountDone). newColor green: g + (((end green) - g) * amountDone). newColor blue: b + (((end blue) - b) * amountDone). newColor alpha: a + (((end alpha) - a) * amountDone). ^ newColor.! !!B3DColor4 class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:22'!numElements ^4! !!B3DColor4 class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 16:21'!r: rValue g: gValue b: bValue a: aValue ^self new r: rValue g: gValue b: bValue a: aValue! !!B3DColor4 class methodsFor: 'instance creation' stamp: 'jsp 2/8/1999 18:46'!red: r green: g blue: b alpha: a "Create an initialize a color vector." | newColor | newColor _ B3DColor4 new. newColor red: r. newColor green: g. newColor blue: b. newColor alpha: a. ^ newColor.! !I am an inplace storage area for B3DColor4 items used during lighting and shading.!!B3DColor4Array methodsFor: 'special ops' stamp: 'ar 2/4/1999 01:50'!+= aColor "Add the given color to all the elements in the receiver" | r g b a | r _ aColor red. g _ aColor green. b _ aColor blue. a _ aColor alpha. 1 to: self basicSize by: 4 do:[:i| self floatAt: i put: (self floatAt: i) + r. self floatAt: i+1 put: (self floatAt: i+1) + g. self floatAt: i+2 put: (self floatAt: i+2) + b. self floatAt: i+3 put: (self floatAt: i+3) + a. ].! !!B3DColor4Array methodsFor: 'special ops' stamp: 'ar 2/7/1999 16:44'!add: aB3dColor4 at: index | baseIdx | baseIdx _ index-1*4. self floatAt: baseIdx+1 put: (self floatAt: baseIdx+1) + aB3dColor4 red. self floatAt: baseIdx+2 put: (self floatAt: baseIdx+2) + aB3dColor4 green. self floatAt: baseIdx+3 put: (self floatAt: baseIdx+3) + aB3dColor4 blue. self floatAt: baseIdx+4 put: (self floatAt: baseIdx+4) + aB3dColor4 alpha.! !!B3DColor4Array methodsFor: 'special ops'!clampAllFrom: minValue to: maxValue "Clamp all elements in the receiver to be in the range (minValue, maxValue)" | value | 1 to: self basicSize do:[:i| value _ self floatAt: i. value _ value min: maxValue. value _ value max: minValue. self floatAt: i put: value. ].! !!B3DColor4Array methodsFor: 'special ops'!fillWith: anInteger <primitive: 145> self primitiveFailed! !!B3DColor4Array class methodsFor: 'instance creation' stamp: 'ar 2/5/1999 22:50'!contentsClass ^B3DColor4! !!B3DDirectionalLight methodsFor: 'shading' stamp: 'ar 2/7/1999 16:54'!computeAttenuationFor: distance "Since a directional light is positioned at virtual infinity, it cannot have any attenuation" ^1.0! !!B3DDirectionalLight methodsFor: 'shading' stamp: 'ar 2/7/1999 16:53'!computeDirectionTo: aB3DPrimitiveVertex "A directional light has an explicit direction regardless of the vertex position" ^direction! !!B3DDirectionalLight methodsFor: 'converting' stamp: 'ar 2/15/1999 21:55'!asPrimitiveLight "Convert the receiver into a B3DPrimitiveLight" | primLight flags | primLight _ B3DPrimitiveLight new. primLight direction: direction. flags _ FlagDirectional. lightColor ambientPart isZero ifFalse:[ primLight ambientPart: lightColor ambientPart. flags _ flags bitOr: FlagAmbientPart]. lightColor diffusePart isZero ifFalse:[ primLight diffusePart: lightColor diffusePart. flags _ flags bitOr: FlagDiffusePart]. lightColor specularPart isZero ifFalse:[ primLight specularPart: lightColor specularPart. flags _ flags bitOr: FlagSpecularPart]. primLight flags: flags. ^primLight! !!B3DDirectionalLight methodsFor: 'converting' stamp: 'ar 2/8/1999 01:28'!transformedBy: aTransformer ^(super transformedBy: aTransformer) direction: (aTransformer transformDirection: direction)! !I represent a hardware accelerated 3D display. Usually, this means some sort of offscreen buffer (so that we can do efficient compositing for the 2D case) but it might be different.The first implementation uses Direct3D on Windows where compositing is trivially achieved by using DirectDrawSurfaces which can be accessed by either 2D or 3D operations.!!B3DDisplayScreen methodsFor: 'testing' stamp: 'ar 5/27/2000 17:16'!isB3DDisplayScreen ^true! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:47'!primBltFast: displayHandle from: sourceHandle at: destOrigin from: sourceOrigin extent: extent <primitive:'primitiveBltToDisplay' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/28/2000 01:47'!primBltFast: displayHandle to: dstHandle at: destOrigin from: sourceOrigin extent: extent "Primitive. Perform a fast blt operation. Return the receiver if successful." <primitive:'primitiveBltFromDisplay' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:18'!primCreateDisplaySurface: d width: w height: h "Primitive. Create a new external display surface. Return the handle used to identify the receiver. Fail if the surface cannot be created." <primitive:'primitiveCreateDisplaySurface' module: 'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:18'!primDestroyDisplaySurface: aHandle "Primitive. Destroy the display surface associated with the given handle." <primitive: 'primitiveDestroyDisplaySurface' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:19'!primDisplay: aHandle colorMasksInto: anArray "Primitive. Store the bit masks for each color into the given array." <primitive: 'primitiveDisplayGetColorMasks' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:19'!primFill: handle color: pixelWord x: x y: y w: w h: h "Primitive. Perform an accelerated fill operation on the receiver." <primitive:'primitiveFillDisplaySurface' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:20'!primFinish: aHandle "Primitive. Finish all rendering operations on the receiver. Do not return before all rendering operations have taken effect." <primitive: 'primitiveFinishDisplaySurface' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:21'!primFlush: aHandle "Primitive. If any rendering operations are pending, force them to be executed. Do not wait until they have taken effect." <primitive: 'primitiveFlushDisplaySurface' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-display' stamp: 'ar 5/27/2000 17:21'!supportsDisplayDepth: pixelDepth "Return true if this pixel depth is supported on the current host platform." <primitive: 'primitiveSupportsDisplayDepth' module:'Squeak3DX'> ^false! !!B3DDisplayScreen methodsFor: 'primitives-forms' stamp: 'ar 5/27/2000 17:21'!primAllocateForm: d width: w height: h "Primitive. Allocate a form with the given parameters" <primitive:'primitiveAllocateForm' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-forms' stamp: 'ar 5/27/2000 17:22'!primDestroyForm: aHandle "Primitive. Destroy the form associated with the given handle." <primitive:'primitiveDestroyForm' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-forms' stamp: 'ar 5/27/2000 17:22'!primForm: aHandle colorMasksInto: anArray "Primitive. Store the bit masks for each color into the given array." <primitive: 'primitiveFormGetColorMasks' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 20:21'!primAllocateTexture: d width: w height: h "Primitive. Allocate a texture with the given dimensions. Note: The texture allocated may *not* match the specified values here." <primitive:'primitiveAllocateTexture' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 17:23'!primDestroyTexture: aHandle "Primitive. Destroy the texture associated with the given handle." <primitive:'primitiveDestroyTexture' module:'Squeak3DX'> ^nil! !!B3DDisplayScreen methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 17:23'!primGetTextureDepth: aHandle "Primitive. Return the actual depth of the texture with the given handle" <primitive:'primitiveTextureDepth' module:'Squeak3DX'> ^self primitiveFailed! !!B3DDisplayScreen methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 17:24'!primGetTextureHeight: aHandle "Primitive. Return the actual height of the texture with the given handle" <primitive:'primitiveTextureHeight' module:'Squeak3DX'> ^self primitiveFailed! !!B3DDisplayScreen methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 17:24'!primGetTextureWidth: aHandle "Primitive. Return the actual width of the texture with the given handle" <primitive:'primitiveTextureWidth' module:'Squeak3DX'> ^self primitiveFailed! !!B3DDisplayScreen methodsFor: 'primitives-textures' stamp: 'ar 5/27/2000 17:24'!primTexture: aHandle colorMasksInto: anArray "Primitive. Store the bit masks for each color into the given array." <primitive: 'primitiveTextureGetColorMasks' module:'Squeak3DX'> ^nil! !I am the superclass for all separate parts of the Balloon 3D engine. I define the basic interface each part of the engine must respond to.Instance variables: engine <B3DRenderEngine> The 3D engine I am associated with!!B3DEnginePart methodsFor: 'initialize' stamp: 'ar 2/16/1999 01:47'!destroy "Destroy all resources temporarily assigned to the receiver"! !!B3DEnginePart methodsFor: 'initialize' stamp: 'ar 2/5/1999 21:34'!flush "Flush all pending operations"! !!B3DEnginePart methodsFor: 'initialize'!initialize! !!B3DEnginePart methodsFor: 'initialize' stamp: 'ar 4/10/1999 22:52'!reset! !!B3DEnginePart methodsFor: 'private'!setEngine: aB3DRenderEngine engine _ aB3DRenderEngine! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/7/1999 03:39'!processIndexedLines: vb "Process an indexed line set"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/8/1999 15:36'!processIndexedQuads: vb "Process an indexed quad set"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/7/1999 03:39'!processIndexedTriangles: vb "Process an indexed triangle set"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/4/1999 04:21'!processLineLoop: vertexBuffer "Process a closed line defined by the vertex buffer"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/4/1999 04:21'!processLines: vertexBuffer "Process a series of lines defined by each two points the vertex buffer"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/4/1999 04:21'!processPoints: vertexBuffer "Process a series of points defined by the vertex buffer"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/4/1999 04:22'!processPolygon: vertexBuffer "Process a polygon defined by the vertex buffer"! !!B3DEnginePart methodsFor: 'processing' stamp: 'ar 2/8/1999 15:35'!processVertexBuffer: vb "Process the given vertex buffer in this part of the engine." ^self perform: (PrimitiveActions at: vb primitive) with: vb! !!B3DEnginePart class methodsFor: 'instance creation'!engine: aB3DRenderEngine ^self new setEngine: aB3DRenderEngine! !!B3DEnginePart class methodsFor: 'instance creation'!new ^super new initialize! !!B3DEnginePart class methodsFor: 'class initialization' stamp: 'ar 2/7/1999 19:52'!initialize "B3DEnginePart initialize" PrimitiveActions _ #( processPoints: processLines: processPolygon: processIndexedLines: processIndexedTriangles: processIndexedQuads: ).! !!B3DEnginePart class methodsFor: 'testing' stamp: 'ar 2/14/1999 01:39'!isAvailable "Return true if this part of the engine is available" ^self subclassResponsibility! !!B3DEnginePart class methodsFor: 'testing' stamp: 'ar 2/17/1999 04:39'!isAvailableFor: anOutputMedium "Return true if this part of the engine is available for the given output medium" ^self isAvailable! !I am a generic superclass for all Balloon 3D plugins.!!B3DEnginePlugin methodsFor: 'primitive support' stamp: 'ar 2/14/1999 00:01'!stackMatrix: index "Load a 4x4 transformation matrix from the interpreter stack. Return a pointer to the matrix data if successful, nil otherwise." | oop | self inline: false. self returnTypeC:'void*'. oop _ interpreterProxy stackObjectValue: index. oop = nil ifTrue:[^nil]. ((interpreterProxy isWords: oop) and:[(interpreterProxy slotSizeOf: oop) = 16]) ifTrue:[^interpreterProxy firstIndexableField: oop]. ^nil! !!B3DEnginePlugin methodsFor: 'primitive support' stamp: 'ar 4/12/1999 02:15'!stackPrimitiveIndexArray: stackIndex ofSize: nItems validate: aBool forVertexSize: maxIndex "Load a primitive index array from the interpreter stack. If aBool is true then check that all the indexes are in the range (1,maxIndex). Return a pointer to the index data if successful, nil otherwise." | oop oopSize idxPtr index | self inline: false. self returnTypeC:'void*'. self var: #idxPtr declareC:'int *idxPtr'. oop _ interpreterProxy stackObjectValue: stackIndex. oop = nil ifTrue:[^nil]. (interpreterProxy isWords: oop) ifFalse:[^nil]. oopSize _ interpreterProxy slotSizeOf: oop. oopSize < nItems ifTrue:[^nil]. idxPtr _ self cCoerce: (interpreterProxy firstIndexableField: oop) to:'int *'. aBool ifTrue:[ 0 to: nItems-1 do:[:i| index _ idxPtr at: i. (index < 0 or:[index > maxIndex]) ifTrue:[^nil]]]. ^idxPtr! !!B3DEnginePlugin methodsFor: 'primitive support' stamp: 'ar 2/14/1999 00:00'!stackPrimitiveVertex: index "Load a primitive vertex from the interpreter stack. Return a pointer to the vertex data if successful, nil otherwise." | oop | self inline: false. self returnTypeC:'void*'. oop _ interpreterProxy stackObjectValue: index. oop = nil ifTrue:[^nil]. ((interpreterProxy isWords: oop) and:[(interpreterProxy slotSizeOf: oop) = PrimVertexSize]) ifTrue:[^interpreterProxy firstIndexableField: oop]. ^nil! !!B3DEnginePlugin methodsFor: 'primitive support' stamp: 'ar 2/14/1999 00:00'!stackPrimitiveVertexArray: index ofSize: nItems "Load a primitive vertex array from the interpreter stack. Return a pointer to the vertex data if successful, nil otherwise." | oop oopSize | self inline: false. self returnTypeC:'void*'. oop _ interpreterProxy stackObjectValue: index. oop = nil ifTrue:[^nil]. (interpreterProxy isWords: oop) ifTrue:[ oopSize _ interpreterProxy slotSizeOf: oop. (oopSize >= nItems * PrimVertexSize and:[oopSize \\ PrimVertexSize = 0]) ifTrue:[^interpreterProxy firstIndexableField: oop]]. ^nil! !!B3DEnginePlugin methodsFor: 'initialize-release' stamp: 'ar 5/16/2000 20:05'!initialiseModule self export: true. loadBBFn _ interpreterProxy ioLoadFunction: 'loadBitBltFrom' From: bbPluginName. copyBitsFn _ interpreterProxy ioLoadFunction: 'copyBitsFromtoat' From: bbPluginName. ^(loadBBFn ~= 0 and:[copyBitsFn ~= 0])! !!B3DEnginePlugin methodsFor: 'initialize-release' stamp: 'ar 5/16/2000 20:05'!moduleUnloaded: aModuleName "The module with the given name was just unloaded. Make sure we have no dangling references." self export: true. self var: #aModuleName type: 'char *'. (aModuleName strcmp: bbPluginName) = 0 ifTrue:[ "BitBlt just shut down. How nasty." loadBBFn _ 0. copyBitsFn _ 0. ].! !!B3DEnginePlugin class methodsFor: 'translation' stamp: 'ar 5/16/2000 20:05'!declareCVarsIn: cg cg var: 'bbPluginName' declareC:'char bbPluginName[256] = "BitBltPlugin"'.! !!B3DEnginePlugin class methodsFor: 'translation' stamp: 'ar 2/8/1999 20:48'!moduleName ^'Squeak3D'! !!B3DEnginePlugin class methodsFor: 'translation' stamp: 'TPR 5/23/2000 17:26'!translate: fileName doInlining: inlineFlag locally: localFlag "Time millisecondsToRun: [ FloatArrayPlugin translate: 'SqFloatArray.c' doInlining: true. Smalltalk beep]" | cg fullName fd | fullName _ self baseDirectoryName. fd _ FileDirectory on: fullName. localFlag ifFalse:[ (fd directoryExists: self moduleName) ifFalse:[fd createDirectory: self moduleName]. fd _ fd on: (fd fullNameFor: self moduleName)]. fullName _ fd fullNameFor: fileName. self initialize. self headerFile ifNotNil:[ (CrLfFileStream newFileNamed: (fd fullNameFor: self moduleName,'.h')) nextPutAll: self headerFile; close]. cg _ self codeGeneratorClass new initialize. localFlag ifTrue:[cg pluginPrefix: self moduleName]. "Add an extra declaration for module name" cg declareModuleName: self moduleNameAndVersion local: localFlag. {InterpreterPlugin. B3DEnginePlugin. B3DTransformerPlugin. B3DVertexBufferPlugin. B3DShaderPlugin. B3DClipperPlugin. B3DPickerPlugin. B3DRasterizerPlugin} do: [:theClass | theClass initialize. cg addClass: theClass. theClass declareCVarsIn: cg]. cg storeCodeOnFile: fullName doInlining: inlineFlag. B3DRasterizerPlugin writeSupportCode: true. ^cg! !!B3DEnginePlugin class methodsFor: 'translation' stamp: 'TPR 5/23/2000 17:26'!translateB3D "B3DEnginePlugin translateB3D" "Translate all the basic plugins into one support module and write the C sources for the rasterizer." | cg | cg _ PluggableCodeGenerator new initialize. cg declareModuleName: self moduleNameAndVersion local: false. {InterpreterPlugin. B3DEnginePlugin. B3DTransformerPlugin. B3DVertexBufferPlugin. B3DShaderPlugin. B3DClipperPlugin. B3DPickerPlugin. B3DRasterizerPlugin} do: [:theClass | theClass initialize. cg addClass: theClass. theClass declareCVarsIn: cg]. cg storeCodeOnFile: self moduleName , '.c' doInlining: true. " cg storeCodeOnFile: '/tmp/Ballon3D.c' doInlining: true." B3DRasterizerPlugin writeSupportCode: true! !I represent a lookup table for several exponents during lighting. Values are computed based on linear interpolation between the stored elements. New tables are created by providing a one argument initialization block from which I am created.!!B3DExponentTable methodsFor: 'initialize' stamp: 'ar 2/8/1999 00:08'!initializeFrom: aBlock | last next | last _ nil. 1 to: self size // 2 do:[:i| next _ aBlock value: (i-1) / (self size // 2 - 1) asFloat. (next isInfinite or:[next isNaN]) ifTrue:[next _ 0.0]. self at: i*2-1 put: next. i > 1 ifTrue:[self at: i-1*2 put: next - last]. last _ next. ].! !!B3DExponentTable methodsFor: 'accessing' stamp: 'ar 2/8/1999 00:10'!valueAt: aFloat "Return the table approximation for the given float value" | index max | aFloat < 0.0 ifTrue:[^self error:'Cannot use negative numbers in table lookup']. max _ self size // 2. index _ (max * aFloat) asInteger + 1. index >= max ifTrue:[^self at: self size-1]. "Linear interpolation inbetween" ^(self at: index) + (aFloat - (index-1) * (self at: index+1))! !!B3DExponentTable class methodsFor: 'class initialization' stamp: 'ar 2/8/1999 00:02'!initialize "B3DExponentTable initialize" DefaultExponents _ Dictionary new. 0 to: 2 do:[:i| DefaultExponents at: i put: (self using:[:value| value raisedTo: i]). ].! !!B3DExponentTable class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 23:56'!new ^self using:[:value| value]! !!B3DExponentTable class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 23:55'!numElements ^128! !!B3DExponentTable class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 23:59'!using: aBlock "Create a new exponent table using aBlock as initialization" ^super new initializeFrom: aBlock! !!B3DFillList methodsFor: 'initialize' stamp: 'ar 4/4/1999 04:28'!initialize self reset.! !!B3DFillList methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:39'!first ^firstFace! !!B3DFillList methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:49'!last ^lastFace! !!B3DFillList methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:31'!reset firstFace _ lastFace _ nil.! !!B3DFillList methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:00'!searchForNewTopAtX: xValue y: yValue "A top face ended with no known right face. We have to search the fill list for the face with the smallest z value. Note: In theory, this should only happen on *right* boundaries of meshes and thus not affect performance too much. Having the fillList sorted by its minimal z value should help, too." | face topFace topZ faceZ floatX floatY | self isEmpty ifTrue:[^self]. "No top" floatX _ xValue / 4096.0. floatY _ yValue. face _ self first. topFace _ face. topZ _ face zValueAtX: floatX y: floatY. [face _ face nextFace. face == nil] whileFalse:[ face minZ > topZ ifTrue:[ "Done. Everything else is behind." self remove: topFace. self addFront: topFace. ^self]. faceZ _ face zValueAtX: floatX y: floatY. faceZ < topZ ifTrue:[ topZ _ faceZ. topFace _ face]]. self remove: topFace. self addFront: topFace.! !!B3DFillList methodsFor: 'accessing' stamp: 'ar 4/4/1999 23:53'!size | n face | n _ 0. face _ firstFace. [face == nil] whileFalse:[ n _ n + 1. face _ face nextFace. ]. ^n! !!B3DFillList methodsFor: 'adding' stamp: 'ar 4/5/1999 20:38'!addBack: aFace "Add the given face as a non-front face (e.g., insert it after the front face). Make sure that the receiver stays sorted by the minimal z values of faces." | minZ midZ face | firstFace == nil ifTrue:[^self error:'Inserting a back face with no front face']. minZ _ aFace minZ. "Quick optimization for insertion at end" (firstFace == lastFace or:[minZ >= lastFace minZ]) ifTrue:[^self addLast: aFace]. "Try an estimation for how to search" midZ _ (firstFace nextFace minZ + lastFace minZ) * 0.5. minZ <= midZ ifTrue:[ "Search front to back" face _ firstFace nextFace. [face minZ < minZ] whileTrue:[face _ face nextFace]. ] ifFalse:[ "Search back to front" face _ lastFace prevFace. "Already checked for lastFace minZ < face minZ" [face minZ > minZ] whileTrue:[face _ face prevFace]. face _ face nextFace. ]. self insert: aFace before: face.! !!B3DFillList methodsFor: 'adding' stamp: 'ar 4/18/1999 08:04'!addFirst: aFace firstFace isNil ifTrue:[lastFace _ aFace] ifFalse:[firstFace prevFace: aFace]. aFace nextFace: firstFace. aFace prevFace: nil. firstFace _ aFace. B3DScanner doDebug ifTrue:[self validate].! !!B3DFillList methodsFor: 'adding' stamp: 'ar 4/5/1999 20:41'!addFront: aFace "Add the given face as the new front face. Make sure the sort order stays okay." | backFace minZ tempFace | firstFace == lastFace ifFalse:["firstFace == lastFace denotes 0 or 1 elements" backFace _ firstFace nextFace. minZ _ firstFace minZ. [backFace notNil and:[backFace minZ < minZ]] whileTrue:[backFace _ backFace nextFace]. "backFace contains the face before which firstFace has to be added" firstFace nextFace == backFace ifFalse:[ tempFace _ firstFace. self remove: tempFace. backFace == nil ifTrue:[self addLast: tempFace] ifFalse:[self insert: tempFace before: backFace]. ]. ]. ^self addFirst: aFace! !!B3DFillList methodsFor: 'adding' stamp: 'ar 4/18/1999 08:04'!addLast: aFace lastFace isNil ifTrue:[firstFace _ aFace] ifFalse:[lastFace nextFace: aFace]. aFace prevFace: lastFace. aFace nextFace: nil. lastFace _ aFace. B3DScanner doDebug ifTrue:[self validate].! !!B3DFillList methodsFor: 'adding' stamp: 'ar 4/18/1999 08:04'!insert: aFace before: nextFace "Insert the given face before nextFace." B3DScanner doDebug ifTrue:[ (self includes: nextFace) ifFalse:[^self error:'Face not in collection']. (self includes: aFace) ifTrue:[^self error:'Face already in collection']. ]. aFace nextFace: nextFace. aFace prevFace: nextFace prevFace. aFace prevFace nextFace: aFace. nextFace prevFace: aFace. B3DScanner doDebug ifTrue:[self validate].! !!B3DFillList methodsFor: 'removing' stamp: 'ar 4/18/1999 08:04'!remove: aFace (B3DScanner doDebug and:[(self includes: aFace) not]) ifTrue:[^self error:'Face not in list']. B3DScanner doDebug ifTrue:[self validate]. aFace prevFace isNil ifTrue:[firstFace _ aFace nextFace] ifFalse:[aFace prevFace nextFace: aFace nextFace]. aFace nextFace isNil ifTrue:[lastFace _ aFace prevFace] ifFalse:[aFace nextFace prevFace: aFace prevFace]. ^aFace! !!B3DFillList methodsFor: 'enumerating' stamp: 'ar 4/18/1999 08:03'!do: aBlock | face | B3DScanner doDebug ifTrue:[self validate]. face _ firstFace. [face == nil] whileFalse:[ aBlock value: face. face _ face nextFace. ].! !!B3DFillList methodsFor: 'testing' stamp: 'ar 4/5/1999 01:58'!includes: aFace | face | face _ firstFace. [face == nil] whileFalse:[ face == aFace ifTrue:[^true]. face _ face nextFace. ]. ^false! !!B3DFillList methodsFor: 'testing' stamp: 'ar 4/3/1999 00:49'!isEmpty ^firstFace == nil! !!B3DFillList methodsFor: 'private' stamp: 'ar 4/5/1999 03:54'!printOn: aStream super printOn: aStream. aStream nextPut:$(; print: self size; nextPut: $).! !!B3DFillList methodsFor: 'private' stamp: 'ar 4/5/1999 20:27'!validate | face | (firstFace == nil and:[lastFace == nil]) ifTrue:[^self]. firstFace prevFace == nil ifFalse:[^self error:'Bad list']. lastFace nextFace == nil ifFalse:[^self error:'Bad list']. face _ firstFace. [face == lastFace] whileFalse:[face _ face nextFace]. self validateSortOrder.! !!B3DFillList methodsFor: 'private' stamp: 'ar 4/5/1999 20:39'!validateSortOrder | backFace | firstFace == lastFace ifTrue:[^self]. "0 or 1 element" backFace _ firstFace nextFace. [backFace nextFace == nil] whileFalse:[ backFace minZ <= backFace nextFace minZ ifFalse:[^self error:'Sorting error']. backFace _ backFace nextFace. ].! !!B3DFillList class methodsFor: 'instance creation' stamp: 'ar 4/4/1999 04:27'!new ^super new initialize! !I am the superclass for all Balloon 3D vector objects.!!B3DFloatArray methodsFor: 'accessing'!floatAt: index "For subclasses that override #at:" <primitive: 'primitiveFloatArrayAt'> ^Float fromIEEE32Bit: (self basicAt: index)! !!B3DFloatArray methodsFor: 'accessing'!floatAt: index put: value "For subclasses that override #at:put:" <primitive: 'primitiveFloatArrayAtPut'> self basicAt: index put: value asIEEE32BitWord. ^value! !!B3DFloatArray methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:23'!numElements ^self class numElements! !!B3DFloatArray methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:10'!wordAt: index <primitive: 60> ^self primitiveFailed! !!B3DFloatArray methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:10'!wordAt: index put: value <primitive: 61> ^self primitiveFailed! !!B3DFloatArray methodsFor: 'initialize'!loadFrom: srcObject self == srcObject ifTrue:[^self]. self class == srcObject class ifTrue:[self replaceFrom: 1 to: self size with: srcObject startingAt: 1] ifFalse:[self privateLoadFrom: srcObject]! !!B3DFloatArray methodsFor: 'private'!privateLoadFrom: srcObject "Load the receiver from the given source object." self error:'Cannot load a ', srcObject class name,' into a ', self class name.! !!B3DFloatArray class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:20'!new ^super new: self numElements! !!B3DFloatArray class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:21'!numElements ^0! !B3DHardwareEngine is a render engine specifically designed to deal with HW accellerated implementations. The (currently only) difference to the generic render engine is that a HW accellerated engine automatically clips the virtual viewport specified by client. This is necessary since HW accellerated rasterizers can usually not render outside the actual display surface.Note: If the viewport clipping proves to be efficient enough it might be promoted to the general render engine since there is no point in rendering outside the clipping rectangle.!!B3DHardwareEngine methodsFor: 'accessing' stamp: 'ar 5/28/2000 04:05'!viewport: aRectangle "check if we need a transform override for the viewport" | vp clipRect | vp _ aRectangle. clipRect _ rasterizer clipRect. (clipRect containsRect: vp) ifTrue:[ "Good. The viewport is fully within the clip rect." vpTransform _ nil. ] ifFalse:[ "We need a transform override here" vp _ clipRect intersect: vp. "Actual viewport is vp. Now scale from aRectangle into vp. This is equivalent to picking vp center with vp extent." vp area > 0 ifTrue:[ vpTransform _ self pickingMatrixFor: aRectangle at: (vp origin + vp corner) * 0.5 extent: vp extent]. ]. "And set actual viewport" super viewport: vp.! !!B3DHardwareEngine methodsFor: 'private-rendering' stamp: 'ar 2/27/2000 20:14'!privateTransformVB: vb vpTransform ifNil:[^transformer processVertexBuffer: vb] ifNotNil:["We must override the projection matrix here" ^transformer processVertexBuffer: vb modelView: transformer modelViewMatrix projection: (transformer projectionMatrix composedWithGlobal: vpTransform)].! !!B3DHardwareEngine class methodsFor: 'accessing' stamp: 'ar 2/24/2000 00:15'!rasterizer ^B3DHardwareRasterizer! !WICHTIG: Viewport muss an den renderer gebunden sein. Viewport kann multiple sein.!!B3DHardwareRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:13'!finish "Wait until drawing was completed so we won't get into any trouble with 2D operations afterwards. Note: Later we will synchronize this with the portions of display in use." target finish! !!B3DHardwareRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:13'!flush "Flush the pipeline. Flushing will force processing but not wait until it's finished." target flush.! !!B3DHardwareRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:28'!viewport: vp super viewport: vp. self primSetViewportX: viewport left y: viewport top w: viewport width h: viewport height.! !!B3DHardwareRasterizer methodsFor: 'accessing' stamp: 'ar 5/27/2000 00:47'!clearDepthBuffer self primClearDepthBuffer.! !!B3DHardwareRasterizer methodsFor: 'testing' stamp: 'ar 2/24/2000 00:00'!needsClip ^true! !!B3DHardwareRasterizer methodsFor: 'processing' stamp: 'ar 5/27/2000 17:27'!processVertexBuffer: vb self primProcessVB: vb primitive texture: (target textureHandleOf: texture) vertices: vb vertexArray vertexCount: vb vertexCount faces: vb indexArray faceCount: vb indexCount. ^nil! !!B3DHardwareRasterizer methodsFor: 'primitives' stamp: 'ar 5/26/2000 15:06'!primClearDepthBuffer <primitive:'primitiveClearDepthBuffer' module:'Squeak3DX'> ^self primitiveFailed! !!B3DHardwareRasterizer methodsFor: 'primitives' stamp: 'ar 5/26/2000 12:49'!primProcessVB: primitiveType texture: textureHandle vertices: vtxArray vertexCount: vtxCount faces: idxArray faceCount: idxCount <primitive:'primitiveProcessVertexBuffer' module:'Squeak3DX'> ^self primitiveFailed! !!B3DHardwareRasterizer methodsFor: 'primitives' stamp: 'ar 2/24/2000 00:06'!primSetViewportX: left y: top w: width h: height <primitive:'primitiveSetViewport' module:'Squeak3DX'> ^self primitiveFailed! !!B3DHardwareRasterizer class methodsFor: 'accessing' stamp: 'ar 5/25/2000 22:00'!isAvailable ^self version > 0! !!B3DHardwareRasterizer class methodsFor: 'accessing' stamp: 'ar 5/25/2000 22:01'!version "B3DPrimitiveRasterizer version" <primitive:'primitiveRasterizerVersion' module:'Squeak3DX'> ^0! !!B3DHardwareRasterizer class methodsFor: 'testing' stamp: 'ar 5/28/2000 15:04'!isAvailableFor: aForm "Return true if this part of the engine is available for the given output medium" aForm ifNil:[^false]. (aForm isDisplayScreen and:[aForm isB3DDisplayScreen]) ifFalse:[^false]. ^self isAvailable! !I represent a generic indexed face mesh. My subclasses define what kind of primitive objects I can represent. !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 2/16/1999 19:08'!boundingBox ^bBox ifNil:[bBox _ self computeBoundingBox]! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 2/16/1999 19:08'!faceNormals ^faceNormals ifNil:[faceNormals _ self computeFaceNormals]! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 2/16/1999 19:08'!faces ^faces! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'jsp 3/11/1999 11:44'!faces: newFaces faces _ newFaces.! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 2/16/1999 19:08'!texCoords ^vtxTexCoords! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'jsp 3/11/1999 11:43'!texCoords: newTexCoords vtxTexCoords _ newTexCoords.! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 9/16/1999 14:49'!vertexColors ^vtxColors! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 9/16/1999 14:50'!vertexColors: aB3DColor4Array vtxColors _ aB3DColor4Array! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 2/16/1999 19:08'!vertexNormals ^vtxNormals ifNil:[vtxNormals _ self computeVertexNormals].! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'jsp 3/11/1999 11:44'!vertexNormals: newNormals vtxNormals _ newNormals.! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'ar 2/16/1999 19:08'!vertices ^vertices! !!B3DIndexedMesh methodsFor: 'accessing' stamp: 'jsp 3/11/1999 11:43'!vertices: newVertices vertices _ newVertices.! !!B3DIndexedMesh methodsFor: 'modifying' stamp: 'ar 2/16/1999 19:08'!centerAtZero self translateBy: (self boundingBox origin + self boundingBox corner * -0.5).! !!B3DIndexedMesh methodsFor: 'modifying' stamp: 'jsp 9/17/1999 14:13'!transformBy: aMatrix "Modify the mesh by transforming it using a matrix; this allows us to change the insertion point of the mesh" vertices do: [:vtx | vtx privateLoadFrom: ((aMatrix composeWith: (B3DMatrix4x4 identity translation: vtx)) translation) ]. bBox ifNotNil: [ self computeBoundingBox ]. self computeVertexNormals.! !!B3DIndexedMesh methodsFor: 'modifying' stamp: 'ar 2/16/1999 19:08'!translateBy: amount vertices do:[:vtx| vtx += amount]. bBox ifNotNil:[bBox _ bBox translateBy: amount].! !!B3DIndexedMesh methodsFor: 'displaying' stamp: 'ar 2/16/1999 19:08'!renderOn: aRenderer ^self subclassResponsibility! !!B3DIndexedMesh methodsFor: 'private' stamp: 'ar 2/16/1999 19:08'!computeBoundingBox | min max | min _ max _ nil. vertices do:[:vtx| min ifNil:[min _ vtx] ifNotNil:[min _ min min: vtx]. max ifNil:[max _ vtx] ifNotNil:[max _ max max: vtx]. ]. ^Rectangle origin: min corner: max! !!B3DIndexedMesh methodsFor: 'private' stamp: 'ar 2/16/1999 19:09'!computeFaceNormals | out face v1 v2 v3 d1 d2 normal | out _ B3DVector3Array new: faces size. 1 to: faces size do:[:i| face _ faces at: i. v1 _ vertices at: face p1Index. v2 _ vertices at: face p2Index. v3 _ vertices at: face p3Index. d1 _ v3 - v1. d2 _ v2 - v1. d1 safelyNormalize. d2 safelyNormalize. normal _ d1 cross: d2. out at: i put: normal safelyNormalize. ]. ^out! !!B3DIndexedMesh methodsFor: 'private' stamp: 'ar 2/16/1999 19:09'!computeVertexNormals | temp normals face normal v1 v2 v3 out | temp _ Array new: vertices size. 1 to: temp size do:[:i| temp at: i put: B3DVector4 new]. normals _ self faceNormals. "Forces computation if necessary" 1 to: faces size do:[:i| face _ faces at: i. normal _ (normals at: i) asB3DVector4. v1 _ face p1Index. v2 _ face p2Index. v3 _ face p3Index. (temp at: v1) += normal. (temp at: v2) += normal. (temp at: v3) += normal. ]. out _ B3DVector3Array new: vertices size. 1 to: out size do:[:i| out at: i put: (temp at: i) asB3DVector3 safelyNormalize. ]. ^out! !!B3DIndexedMesh methodsFor: 'optimizations' stamp: 'ar 2/8/1999 06:52'!optimizeMeshLayout "Optimize the layout of the indexed mesh for primitive operations. Optimzed layouts include triangle/quad strips and fans and will result in MUCH better performance during rendering. However, optimizations are generally time-consuming so you better don't call this method too often." ^self "Must be implemented in my subclasses"! !!B3DIndexedMesh methodsFor: 'converting' stamp: 'ar 9/17/1999 12:37'!asSimpleMesh "Convert the receiver into a very simple mesh representation" | simpleFaces oldFace newVtx newFace newVertices pos | simpleFaces _ WriteStream on: (Array new: faces size). newVertices _ WriteStream on: (Array new: 10). 1 to: faces size do:[:i| oldFace _ faces at: i. newVertices reset. 1 to: oldFace size do:[:j| pos _ oldFace at: j. newVtx _ B3DSimpleMeshVertex new. newVtx position: (vertices at: pos). vtxNormals == nil ifFalse:[newVtx normal: (vtxNormals at: pos)]. vtxColors == nil ifFalse:[newVtx color: (vtxColors at: pos)]. vtxTexCoords == nil ifFalse:[newVtx texCoord: (vtxTexCoords at: pos)]. newVertices nextPut: newVtx]. newFace _ B3DSimpleMeshFace withAll: newVertices contents. simpleFaces nextPut: newFace]. ^B3DSimpleMesh withAll: simpleFaces contents! !!B3DIndexedMesh methodsFor: 'testing' stamp: 'ar 9/16/1999 23:32'!hasVertexColors ^vtxColors notNil! !!B3DIndexedMesh class methodsFor: 'class initialization' stamp: 'ar 9/16/1999 23:02'!flushVRMLCache "B3DIndexedMesh flushVRMLCache" VRML97BoxCache _ VRML97ConeCache _ VRMLCylCache _ VRMLSphereCache _ nil.! !!B3DIndexedMesh class methodsFor: 'class initialization' stamp: 'ar 2/8/1999 06:55'!initialize "B3DIndexedMesh initialize" "Optimization flags: These flags are *hints* and may be ignored by the renderer." FlagStripStart _ 1. FlagFanStart _ 2.! !!B3DIndexedMesh class methodsFor: 'examples' stamp: 'ar 2/8/1999 21:18'!sampleRect ^self sampleRect: 10! !!B3DIndexedMesh class methodsFor: 'examples' stamp: 'ar 2/8/1999 16:58'!sampleRect: n ^self new sampleRect: n! !!B3DIndexedMesh class methodsFor: 'vrml97 prototypes' stamp: 'ar 9/16/1999 22:12'!vrml97Box "Return a mesh representing a VRML97 Box" ^VRML97BoxCache ifNil:[ VRML97BoxCache _ (B3DSimpleMesh withAll: self vrmlCreateBoxFaces) asIndexedMesh]! !!B3DIndexedMesh class methodsFor: 'vrml97 prototypes' stamp: 'ar 9/16/1999 22:15'!vrml97Cone "Return a mesh representing a VRML97 Cone" ^self vrml97Cone: true bottom: true.! !!B3DIndexedMesh class methodsFor: 'vrml97 prototypes' stamp: 'ar 9/16/1999 22:14'!vrml97Cone: doSide bottom: doBottom "Return a mesh representing a VRML97 Cone" | idx | idx _ 0. doBottom ifTrue:[idx _ idx + 2]. doSide ifTrue:[idx _ idx + 1]. VRML97ConeCache == nil ifTrue:[ VRML97ConeCache _ Array new: 3. 1 to: 3 do:[:i| VRML97ConeCache at: i put: (self vrmlCreateCone: (i anyMask: 1) bottom: (i anyMask: 2))]]. ^VRML97ConeCache at: idx! !!B3DIndexedMesh class methodsFor: 'vrml97 prototypes' stamp: 'ar 9/16/1999 22:15'!vrml97Cylinder "Return a mesh representing a VRML97 Cylinder" ^self vrml97Cylinder: true bottom: true top: true.! !!B3DIndexedMesh class methodsFor: 'vrml97 prototypes' stamp: 'ar 9/16/1999 22:14'!vrml97Cylinder: doSide bottom: doBottom top: doTop "Return a mesh representing a VRML97 Cylinder" | idx | idx _ 0. doTop ifTrue:[idx _ idx + 4]. doBottom ifTrue:[idx _ idx + 2]. doSide ifTrue:[idx _ idx + 1]. idx = 0 ifTrue:[^nil]. VRMLCylCache == nil ifTrue:[ VRMLCylCache _ Array new: 7. 1 to: 7 do:[:i| VRMLCylCache at: i put: (self vrmlCreateCylinder: (i anyMask: 1) bottom: (i anyMask: 2) top: (i anyMask: 4))]]. ^VRMLCylCache at: idx! !!B3DIndexedMesh class methodsFor: 'vrml97 prototypes' stamp: 'ar 9/16/1999 22:21'!vrml97Sphere "Return a mesh representing a VRML97 Sphere" ^VRMLSphereCache ifNil:[ VRMLSphereCache _ (B3DSimpleMesh withAll: self vrmlCreateSphereFaces) asIndexedMesh].! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:07'!vrmlCreateBottomFaces | face steps dir m lastVtx nextVtx faceList midVtx | steps _ self vrmlSteps. faceList _ WriteStream on: (Array new: steps). dir _ 0@0@1. m _ (B3DRotation angle: (360.0 / steps) axis: (0@-1@0)) asMatrix4x4. lastVtx _ B3DSimpleMeshVertex new. lastVtx position: 0@-1@1. lastVtx normal: 0@-1@0. lastVtx texCoord: 0.5@1. 1 to: steps do:[:i| face _ B3DSimpleMeshFace new: 3. face at: 1 put: lastVtx. dir _ (m localPointToGlobal: dir) normalized. nextVtx _ B3DSimpleMeshVertex new. nextVtx position: dir x @ -1 @ dir z. nextVtx normal: 0@-1@0. nextVtx texCoord: (dir x @ dir z) * 0.5 + 0.5. midVtx _ nextVtx copy. midVtx position: 0@-1@0. midVtx texCoord: 0.5@0.5. face at: 2 put: nextVtx. face at: 3 put: midVtx. faceList nextPut: face. lastVtx _ nextVtx]. ^faceList contents! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:11'!vrmlCreateBoxFaces | vtx face vtxSpec faceList | faceList _ WriteStream on: (Array new: 6). "front and back face" vtxSpec _ #( ((-1 -1) (0 1)) (( 1 -1) (1 1)) (( 1 1) (1 0)) ((-1 1) (0 0))). "front" face _ B3DSimpleMeshFace new: 4. vtxSpec doWithIndex:[:spec :idx| vtx _ B3DSimpleMeshVertex new. vtx position: spec first first @ spec first second @ -1. vtx normal: 0@0@-1. vtx texCoord: spec second first @ spec second second. face at: idx put: vtx. ]. faceList nextPut: face. "back" face _ B3DSimpleMeshFace new: 4. vtxSpec doWithIndex:[:spec :idx| vtx _ B3DSimpleMeshVertex new. vtx position: spec first first @ spec first second @ 1. vtx normal: 0@0@1. vtx texCoord: 1 - spec second first @ spec second second. face at: idx put: vtx. ]. faceList nextPut: face. "top" face _ B3DSimpleMeshFace new: 4. vtxSpec doWithIndex:[:spec :idx| vtx _ B3DSimpleMeshVertex new. vtx position: spec first first @ 1 @ spec first second. vtx normal: 1@0@0. vtx texCoord: spec second first @ spec second second. face at: idx put: vtx. ]. faceList nextPut: face. "bottom" face _ B3DSimpleMeshFace new: 4. vtxSpec doWithIndex:[:spec :idx| vtx _ B3DSimpleMeshVertex new. vtx position: spec first first @ -1 @ spec first second. vtx normal: -1@0@0. vtx texCoord: spec second first @ (1 - spec second second). face at: idx put: vtx. ]. faceList nextPut: face. vtxSpec _ #( ((-1 -1) (0 1)) ((-1 1) (1 1)) (( 1 1) (1 0)) (( 1 -1) (0 0))). "right" face _ B3DSimpleMeshFace new: 4. vtxSpec doWithIndex:[:spec :idx| vtx _ B3DSimpleMeshVertex new. vtx position: 1 @ spec first first @ spec first second. vtx normal: 1@0@0. vtx texCoord: spec second first @ spec second second. face at: idx put: vtx. ]. faceList nextPut: face. "left" face _ B3DSimpleMeshFace new: 4. vtxSpec doWithIndex:[:spec :idx| vtx _ B3DSimpleMeshVertex new. vtx position: -1 @ spec first first @ spec first second. vtx normal: -1@0@0. vtx texCoord: 1 - spec second first @ spec second second. face at: idx put: vtx. ]. faceList nextPut: face. ^faceList contents! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:16'!vrmlCreateCone: doSide bottom: doBottom | faces | faces _ #(). doSide ifTrue:[faces _ faces, self vrmlCreateConeFaces]. doBottom ifTrue:[faces _ faces, self vrmlCreateBottomFaces]. ^(B3DSimpleMesh withAll: faces) asIndexedMesh! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:07'!vrmlCreateConeFaces | face steps dir m lastVtx nextVtx topVtx faceList | steps _ self vrmlSteps. faceList _ WriteStream on: (Array new: steps). dir _ 0@0@1. m _ (B3DRotation angle: (360.0 / steps) axis: (0@-1@0)) asMatrix4x4. lastVtx _ B3DSimpleMeshVertex new. lastVtx position: 0@-1@1. lastVtx normal: dir. lastVtx texCoord: 0@1. 1 to: steps do:[:i| face _ B3DSimpleMeshFace new: 3. face at: 1 put: lastVtx. dir _ (m localPointToGlobal: dir) normalized. nextVtx _ B3DSimpleMeshVertex new. nextVtx position: dir x @ -1 @ dir z. nextVtx normal: dir. nextVtx texCoord: (i / steps asFloat) @ 1. topVtx _ nextVtx copy. topVtx position: 0@1@0. topVtx texCoord: lastVtx texCoord x @ 0. face at: 2 put: nextVtx. face at: 3 put: topVtx. faceList nextPut: face. lastVtx _ nextVtx]. ^faceList contents! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:05'!vrmlCreateCylinder: doSide bottom: doBottom top: doTop | faces | faces _ #(). doSide ifTrue:[faces _ faces, self vrmlCreateCylinderFaces]. doBottom ifTrue:[faces _ faces, self vrmlCreateBottomFaces]. doTop ifTrue:[faces _ faces, self vrmlCreateTopFaces]. ^(B3DSimpleMesh withAll: faces) asIndexedMesh! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:07'!vrmlCreateCylinderFaces | face steps dir m lastVtx nextVtx topVtx lastTopVtx faceList | steps _ self vrmlSteps. faceList _ WriteStream on: (Array new: steps). dir _ 0@0@1. m _ (B3DRotation angle: (360.0 / steps) axis: (0@-1@0)) asMatrix4x4. lastVtx _ B3DSimpleMeshVertex new. lastVtx position: 0@-1@1. lastVtx normal: dir. lastVtx texCoord: 0@1. lastTopVtx _ lastVtx copy. lastTopVtx position: 0@1@1. lastTopVtx texCoord: 0@0. 1 to: steps do:[:i| face _ B3DSimpleMeshFace new: 4. face at: 1 put: lastVtx. face at: 4 put: lastTopVtx. dir _ (m localPointToGlobal: dir) normalized. nextVtx _ B3DSimpleMeshVertex new. nextVtx position: dir x @ -1 @ dir z. nextVtx normal: dir. nextVtx texCoord: (i / steps asFloat) @ 1. topVtx _ nextVtx copy. topVtx position: dir x @ 1 @ dir z. topVtx texCoord: (i / steps asFloat) @ 0. face at: 2 put: nextVtx. face at: 3 put: topVtx. faceList nextPut: face. lastVtx _ nextVtx. lastTopVtx _ topVtx]. ^faceList contents! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:58'!vrmlCreateSphereFaces "B3DIndexedMesh vrmlCreateSphereFaces" | faceList vtx steps m1 m2 baseDir vtxList vertices dir lastVtx nextVtx face | steps _ self vrmlSteps. faceList _ WriteStream on: (Array new: steps * steps). "<--- vertex construction --->" m1 _ (B3DRotation angle: 360.0 / steps axis: 0@-1@0) asMatrix4x4. m2 _ (B3DRotation angle: 180.0 / steps axis: 1@0@0) asMatrix4x4. baseDir _ 0@1@0. vtxList _ Array new: steps + 1. 0 to: steps do:[:i| i = steps ifTrue:[baseDir _ 0@-1@0]. "Make closed for sure" vertices _ Array new: steps + 1. vtxList at: i+1 put: vertices. dir _ baseDir. 0 to: steps do:[:j| j = steps ifTrue:[dir _ baseDir]. "Make closed for sure" vtx _ B3DSimpleMeshVertex new. vtx position: dir; normal: dir. vtx texCoord: (j / steps asFloat) @ (i / steps asFloat). vertices at: j+1 put: vtx. dir _ (m1 localPointToGlobal: dir) normalized. ]. baseDir _ (m2 localPointToGlobal: baseDir) normalized. ]. "<--- face construction --->" "Construct first round separately as triangles" lastVtx _ vtxList at: 1. nextVtx _ vtxList at: 2. 1 to: steps do:[:i| face _ B3DSimpleMeshFace new: 3. face at: 1 put: (lastVtx at: i). face at: 2 put: (nextVtx at: i+1). face at: 3 put: (nextVtx at: i). faceList nextPut: face]. "Construct the next rounds as quads" 2 to: steps-1 do:[:i| lastVtx _ vtxList at: i. nextVtx _ vtxList at: i+1. 1 to: steps do:[:j| face _ B3DSimpleMeshFace new: 4. face at: 1 put: (lastVtx at: j). face at: 2 put: (lastVtx at: j+1). face at: 3 put: (nextVtx at: j+1). face at: 4 put: (nextVtx at: j). faceList nextPut: face]]. "Construct the last round separately as triangles" lastVtx _ vtxList at: steps. nextVtx _ vtxList at: steps+1. 1 to: steps do:[:i| face _ B3DSimpleMeshFace new: 3. face at: 1 put: (lastVtx at: i). face at: 2 put: (lastVtx at: i+1). face at: 3 put: (nextVtx at: i). faceList nextPut: face]. ^faceList contents! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:08'!vrmlCreateTopFaces | face steps dir m lastVtx nextVtx faceList midVtx | steps _ self vrmlSteps. faceList _ WriteStream on: (Array new: steps). dir _ 0@0@1. m _ (B3DRotation angle: (360.0 / steps) axis: (0@-1@0)) asMatrix4x4. lastVtx _ B3DSimpleMeshVertex new. lastVtx position: 0@1@1. lastVtx normal: 0@1@0. lastVtx texCoord: 0.5@0. 1 to: steps do:[:i| face _ B3DSimpleMeshFace new: 3. face at: 1 put: lastVtx. dir _ (m localPointToGlobal: dir) normalized. nextVtx _ B3DSimpleMeshVertex new. nextVtx position: dir x @ 1 @ dir z. nextVtx normal: 0@1@0. nextVtx texCoord: (dir x @ dir z) * (0.5 @ -0.5) + 0.5. midVtx _ nextVtx copy. midVtx position: 0@1@0. midVtx texCoord: 0.5@0.5. face at: 2 put: nextVtx. face at: 3 put: midVtx. faceList nextPut: face. lastVtx _ nextVtx]. ^faceList contents! !!B3DIndexedMesh class methodsFor: 'vrml support' stamp: 'ar 9/16/1999 22:15'!vrmlSteps "Return the number of steps for rotational objects" ^16! !!B3DIndexedQuad methodsFor: 'initialize' stamp: 'ar 2/7/1999 20:00'!with: i1 with: i2 with: i3 with: i4 self at: 1 put: i1. self at: 2 put: i2. self at: 3 put: i3. self at: 4 put: i4.! !!B3DIndexedQuad methodsFor: 'accessing' stamp: 'ar 2/8/1999 16:39'!flags ^0! !!B3DIndexedQuad methodsFor: 'private' stamp: 'ar 2/7/1999 20:02'!replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." <primitive: 105> ^self primitiveFailed! !!B3DIndexedQuad methodsFor: 'printing' stamp: 'ar 2/8/1999 16:39'!printOn: aStream aStream nextPutAll:'IQuad('; print: (self at: 1); nextPutAll:', '; print: (self at: 2); nextPutAll:', '; print: (self at: 3); nextPutAll:', '; print: (self at: 4); nextPutAll:', '; print: (self flags); nextPutAll:')'.! !!B3DIndexedQuad class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 19:59'!new ^self new: 4! !!B3DIndexedQuad class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 20:03'!numElements ^4! !!B3DIndexedQuad class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 19:59'!with: i1 with: i2 with: i3 with: i4 ^self new with: i1 with: i2 with: i3 with: i4! !!B3DIndexedQuadArray class methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:58'!contentsClass ^B3DIndexedQuad! !!B3DIndexedQuadMesh methodsFor: 'displaying' stamp: 'ar 11/7/1999 18:35'!renderOn: aRenderer ^aRenderer drawIndexedQuads: faces vertices: vertices normals: vtxNormals colors: vtxColors texCoords: vtxTexCoords.! !!B3DIndexedQuadMesh methodsFor: 'private' stamp: 'ar 9/10/1999 15:05'!plainTextureRect "Create a new plain rectangle w/ texture coords" vertices _ B3DVector3Array new: 4. vertices at: 1 put: (-1@-1@0). vertices at: 2 put: (1@-1@0). vertices at: 3 put: (1@1@0). vertices at: 4 put: (-1@1@0). vtxTexCoords _ B3DTexture2Array new: 4. vtxTexCoords at: 1 put: (0@1). vtxTexCoords at: 2 put: (1@1). vtxTexCoords at: 3 put: (1@0). vtxTexCoords at: 4 put: (0@0). faces _ B3DIndexedQuadArray new: 1. faces at: 1 put: (B3DIndexedQuad with: 1 with: 2 with: 3 with: 4).! !!B3DIndexedQuadMesh methodsFor: 'private' stamp: 'ar 2/8/1999 02:15'!sampleRect: n "B3DIndexedQuadMesh new sampleRect" | vtx face | vtx _ WriteStream on: (B3DVector3Array new). n negated to: n do:[:x| n negated to: n do:[:y| vtx nextPut: (B3DVector3 x: x y: y z: 0) /= n asFloat. ]. ]. vertices _ vtx contents. vtxNormals _ B3DVector3Array new: (2*n+1) squared. 1 to: vtxNormals size do:[:i| vtxNormals at: i put: (0@0@-1)]. faces _ B3DIndexedQuadArray new: (2*n) squared. 0 to: 2*n-1 do:[:i| 1 to: 2*n do:[:j| face _ B3DIndexedQuad with: (i*(2*n+1)+j) with: (i*(2*n+1)+j+1) with: (i+1*(2*n+1)+j+1) with: (i+1*(2*n+1)+j). faces at: i*2*n+j put: face. ]].! !!B3DIndexedTriangle methodsFor: 'initialize' stamp: 'ar 2/16/1999 19:09'!with: index1 with: index2 with: index3 self p1Index: index1. self p2Index: index2. self p3Index: index3.! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/8/1999 05:15'!flags ^0 "May be used later"! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/8/1999 05:16'!flags: aNumber ^self "Maybe used later"! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:54'!p1Index ^self at: 1! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:55'!p1Index: aNumber self at: 1 put: aNumber! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:55'!p2Index ^self at: 2! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:55'!p2Index: aNumber self at: 2 put: aNumber! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:55'!p3Index ^self at: 3! !!B3DIndexedTriangle methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:55'!p3Index: aNumber self at: 3 put: aNumber! !!B3DIndexedTriangle methodsFor: 'testing' stamp: 'ar 2/8/1999 06:15'!includesIndex: idx ^(self at: 1) = idx or:[(self at: 2) = idx or:[(self at: 3) = idx]]! !!B3DIndexedTriangle methodsFor: 'private' stamp: 'ar 2/5/1999 23:19'!replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." <primitive: 105> ^self primitiveFailed! !!B3DIndexedTriangle methodsFor: 'printing' stamp: 'ar 2/8/1999 05:14'!printOn: aStream aStream nextPutAll:'IFace('; print: self p1Index; nextPutAll:', '; print: self p2Index; nextPutAll:', '; print: self p3Index; nextPutAll:', '; print: self flags; nextPutAll:')'.! !!B3DIndexedTriangle class methodsFor: 'instance creation' stamp: 'ar 2/8/1999 05:14'!new ^self new: self numElements! !!B3DIndexedTriangle class methodsFor: 'instance creation' stamp: 'ar 2/8/1999 05:15'!numElements ^3! !!B3DIndexedTriangle class methodsFor: 'instance creation' stamp: 'ar 2/16/1999 19:09'!with: index1 with: index2 with: index3 ^self new with: index1 with: index2 with: index3! !!B3DIndexedTriangleArray class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 20:56'!contentsClass ^B3DIndexedTriangle! !!B3DIndexedTriangleMesh methodsFor: 'displaying' stamp: 'ar 11/7/1999 18:35'!renderOn: aRenderer self hasVertexColors ifTrue:[ aRenderer trackAmbientColor: true. aRenderer trackDiffuseColor: true]. ^aRenderer drawIndexedTriangles: faces vertices: vertices normals: vtxNormals colors: vtxColors texCoords: vtxTexCoords.! !!B3DIndexedTriangleMesh methodsFor: 'private' stamp: 'ar 2/8/1999 02:15'!sampleRect: n "B3DIndexedQuadMesh new sampleRect" | vtx face | vtx _ WriteStream on: (B3DVector3Array new). n negated to: n do:[:x| n negated to: n do:[:y| vtx nextPut: (B3DVector3 x: x y: y z: 0) /= n asFloat. ]. ]. vertices _ vtx contents. vtxNormals _ B3DVector3Array new: (2*n+1) squared. 1 to: vtxNormals size do:[:i| vtxNormals at: i put: (0@0@-1)]. faces _ B3DIndexedTriangleArray new: (2*n) squared. 0 to: 2*n-1 do:[:i| 1 to: 2*n do:[:j| face _ B3DIndexedTriangle with: (i*(2*n+1)+j) with: (i*(2*n+1)+j+1) with: (i+1*(2*n+1)+j+1) "with: (i+1*(2*n+1)+j)". faces at: i*2*n+j put: face. "face _ B3DIndexedTriangle with: (i*(2*n+1)+j) with: (i*(2*n+1)+j+1) with: (i+1*(2*n+1)+j+1) with: (i+1*(2*n+1)+j). " ]].! !!B3DIndexedTriangleMesh methodsFor: 'fan creation' stamp: 'ar 2/8/1999 06:42'!makeTriangleFans "Re-arrange the triangles so that they represent triangle fans." | vtxDict avgFacesPerVertex todo done maxShared maxSharedIndex newOrder sharedAssoc | "Compute the average size of faces per vertex (strange measure isn't it ;-)" avgFacesPerVertex _ faces size // vertices size + 3. "So we cover 99% of all cases" "vtxDict contains vertexIndex->(OrderedCollection of: IndexedFace)" vtxDict _ OrderedCollection new: vertices size. "Add all the vertex indexes. The set is larger than necessary to avoid collisions." 1 to: vertices size do:[:i| vtxDict add: i -> (IdentitySet new: avgFacesPerVertex * 3)]. "Go over all faces and add the face to all its vertices. Also store the faces in the toGo list." todo _ IdentitySet new: faces size * 3. done _ IdentitySet new: faces size * 3. faces do:[:iFace| todo add: iFace. (vtxDict at: iFace p1Index) value add: iFace. (vtxDict at: iFace p2Index) value add: iFace. (vtxDict at: iFace p3Index) value add: iFace]. "Now start creating the fans" [todo isEmpty] whileFalse:[ "Let's assume that this method is not called in real-time and spend some time to find the vertex with most shared faces" maxShared _ 0. maxSharedIndex _ nil. vtxDict doWithIndex:[:assoc :index| assoc value size > maxShared ifTrue:[maxShared _ assoc value size. maxSharedIndex _ index]]. maxSharedIndex = nil ifTrue:[^self error:'No shared vertices found']. "Now re-arrange the faces around the shared vertex" sharedAssoc _ vtxDict at: maxSharedIndex. newOrder _ self reArrangeFanFaces: sharedAssoc value around: sharedAssoc key from: todo into: done. "Remove re-arranged faces" newOrder do:[:iFace| (done includes: iFace) ifTrue:[self halt]. todo remove: iFace. done add: iFace. (vtxDict at: iFace p1Index) value remove: iFace ifAbsent:[]. (vtxDict at: iFace p2Index) value remove: iFace ifAbsent:[]. (vtxDict at: iFace p3Index) value remove: iFace ifAbsent:[]]. false ifTrue:[ "Remove the shared index if no more faces left." sharedAssoc value isEmpty ifTrue:[ vtxDict swap: maxSharedIndex with: vtxDict size. "Optimized removal ;-)" vtxDict removeLast]. ]. ].! !!B3DIndexedTriangleMesh methodsFor: 'fan creation' stamp: 'ar 2/8/1999 06:38'!reArrangeFanFaces: sharedFaces around: maxSharedIndex from: todo into: done "Re-arrange the faces in sharedFaces to form a triangle fan. Avoid inplace-reversal of the triangles in doneList -- they have been arranged already" | out next nextIndex prevIndex index | out _ OrderedCollection new: sharedFaces size * 2. next _ sharedFaces detect:[:any| true]. sharedFaces remove: next. out addLast: next. nextIndex _ next p1Index. nextIndex = maxSharedIndex ifTrue:[nextIndex _ next p2Index]. prevIndex _ next p3Index. (prevIndex = maxSharedIndex) ifTrue:[prevIndex _ next p2Index]. "Search forward" [next _ sharedFaces detect:[:iFace| iFace includesIndex: nextIndex] ifNone:[nil]. next notNil] whileTrue:[ sharedFaces remove: next. out addLast: next. index _ next p1Index. (index = maxSharedIndex or:[index = nextIndex]) ifTrue:[ index _ next p2Index. (index = maxSharedIndex or:[index = nextIndex]) ifTrue:[index _ next p3Index]]. nextIndex _ index]. "Search backwards" nextIndex _ prevIndex. [next _ sharedFaces detect:[:iFace| iFace includesIndex: nextIndex] ifNone:[nil]. next notNil] whileTrue:[ sharedFaces remove: next. out addFirst: next. index _ next p1Index. (index = maxSharedIndex or:[index = nextIndex]) ifTrue:[ index _ next p2Index. (index = maxSharedIndex or:[index = nextIndex]) ifTrue:[index _ next p3Index]]. nextIndex _ index]. ^out! !!B3DInplaceArray methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:49'!at: index "Return the primitive vertex at the given index" | vtx | (index < 1 or:[index > self size]) ifTrue:[^self errorSubscriptBounds: index]. vtx _ self contentsClass new. vtx replaceFrom: 1 to: vtx size with: self startingAt: index - 1 * self contentsSize + 1. ^vtx! !!B3DInplaceArray methodsFor: 'accessing' stamp: 'ar 2/6/1999 00:12'!at: index put: anObject "Store the object at the given index in the receiver" | idx | (index < 1 or:[index > self size]) ifTrue:[^self errorSubscriptBounds: index]. idx _ index - 1 * self contentsSize. self privateReplaceFrom: idx+1 to: idx + self contentsSize with: anObject startingAt: 1. ^anObject! !!B3DInplaceArray methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:48'!contentsClass ^self class contentsClass! !!B3DInplaceArray methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:48'!contentsSize ^self contentsClass numElements! !!B3DInplaceArray methodsFor: 'accessing' stamp: 'ar 2/5/1999 22:49'!size "Return the number of primitive vertices that can be stored in the receiver" ^self basicSize // self contentsSize! !!B3DInplaceArray methodsFor: 'copying' stamp: 'ar 2/7/1999 19:48'!copyFrom: start to: stop "Answer a copy of a subset of the receiver, starting from element at index start until element at index stop." | newSize | newSize _ stop - start + 1. ^(self species new: newSize) replaceFrom: 1 to: newSize with: self startingAt: start! !!B3DInplaceArray methodsFor: 'private' stamp: 'ar 2/6/1999 00:39'!privateReplaceFrom: start to: stop with: replacement startingAt: repStart <primitive: 105> start to: stop do:[:i| self basicAt: i put: (replacement at: i - start + repStart). ].! !!B3DInplaceArray methodsFor: 'private' stamp: 'ar 2/7/1999 19:46'!replaceFrom: start to: stop with: replacement startingAt: repStart | max | max _ (replacement size - repStart) min: stop-start. start to: start+max do:[:i| self at: i put: (replacement at: i - start + repStart). ].! !!B3DInplaceArray methodsFor: 'enumerating' stamp: 'ar 2/6/1999 00:37'!do: aBlock "Overridden to store the (possibly) modified argument back" | obj | 1 to: self size do:[:index| obj _ self at: index. aBlock value: obj. self at: index put: obj].! !!B3DInplaceArray methodsFor: 'enumerating' stamp: 'ar 2/6/1999 00:37'!readOnlyDo: aBlock ^super do: aBlock! !!B3DInplaceArray class methodsFor: 'instance creation' stamp: 'ar 2/5/1999 22:48'!contentsClass ^self subclassResponsibility! !!B3DInplaceArray class methodsFor: 'instance creation' stamp: 'ar 2/5/1999 22:49'!contentsSize ^self contentsClass numElements! !!B3DInplaceArray class methodsFor: 'instance creation' stamp: 'ar 2/5/1999 22:49'!new: n ^super new: self contentsSize*n! !I represent the attenuation for any given light source, e.g., how the intensity of the light is reduced with increasing distance from the object. I consist of three parts, a constant part, a linear part and a squared part. The resulting intensity for any given distance d is computed by: intensity _ 1.0 / (constantPart + (distance * linearPart) + (distance^2 * squaredPart)).!!B3DLightAttenuation methodsFor: 'initialize' stamp: 'ar 2/7/1999 19:02'!constant: constantFactor linear: linearFactor squared: squaredFactor self constantPart: constantFactor. self linearPart: linearFactor. self squaredPart: squaredFactor.! !!B3DLightAttenuation methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:44'!constantPart ^self floatAt: 1! !!B3DLightAttenuation methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:45'!constantPart: aNumber self floatAt: 1 put: aNumber! !!B3DLightAttenuation methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:45'!linearPart ^self floatAt: 2! !!B3DLightAttenuation methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:45'!linearPart: aNumber self floatAt: 2 put: aNumber! !!B3DLightAttenuation methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:45'!squaredPart ^self floatAt: 3! !!B3DLightAttenuation methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:45'!squaredPart: aNumber self floatAt: 3 put: aNumber! !!B3DLightAttenuation methodsFor: 'lighting' stamp: 'ar 2/6/1999 18:44'!computeAttenuationFor: distance "Compute the light attenuation for the given distance" ^1.0 / (self constantPart + (distance * (self linearPart + (distance * self squaredPart))))! !!B3DLightAttenuation methodsFor: 'testing' stamp: 'ar 2/15/1999 21:58'!isIdentity "Return true if the attenuation results in a constant lighting" ^self constantPart = 1.0 and:[self linearPart = 0.0 and:[self squaredPart = 0.0]]! !!B3DLightAttenuation class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 19:01'!constant: constantFactor linear: linearFactor squared: squaredFactor ^self new constant: constantFactor linear: linearFactor squared: squaredFactor! !!B3DLightAttenuation class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 18:46'!numElements ^3! !!B3DLightSource methodsFor: 'shading' stamp: 'ar 2/7/1999 16:51'!computeAttenuationFor: distance ^self subclassResponsibility! !!B3DLightSource methodsFor: 'shading' stamp: 'ar 2/7/1999 16:51'!computeDirectionTo: aB3DPrimitiveVertex ^self subclassResponsibility! !!B3DLightSource methodsFor: 'shading' stamp: 'ar 2/15/1999 02:26'!computeSpotFactor: light2Vertex "Compute the spot factor for a spot light" | lightDirection cosAngle minCos deltaCos maxCos | lightDirection _ self direction. cosAngle _ (lightDirection dot: light2Vertex) negated. (cosAngle < (minCos _ self hotSpotMinCosine)) ifTrue:[^0.0]. maxCos _ self hotSpotMaxCosine." maxCos = 1.0 ifFalse:[" deltaCos _ self hotSpotDeltaCosine. deltaCos <= 0.00001 ifTrue:[ "No delta -- a sharp boundary between on and off. Since off has already been determined above, we are on" ^1.0]. "Scale the angle to 0/1 range" cosAngle _ (cosAngle - minCos) / deltaCos. self flag: #TODO. "Don't scale by (maxCos - minCos)"" ]." self flag: #TODO. "Use table lookup for spot exponent" ^cosAngle raisedTo: self spotExponent! !!B3DLightSource methodsFor: 'shading' stamp: 'ar 2/15/1999 03:55'!shadeVertexBuffer: vb with: aMaterial into: colorArray "This is the generic shading function similar to the primitive. Subclasses may implement optimized versions but should evaluate exactly to the same value as in here if they are to be converted into B3DPrimitiveLights." | color vtxArray ambientColor vtx direction distance scale cosAngle diffusePart specularPart specDir specularFactor | self flag: #b3dPrimitive. vtxArray _ vb vertexArray. (self hasAmbientPart and:[vb trackAmbientColor not]) ifTrue:[ambientColor _ aMaterial ambientPart * lightColor ambientPart]. (self hasDiffusePart and:[vb trackDiffuseColor not]) ifTrue:[diffusePart _ aMaterial diffusePart]. (self hasSpecularPart and:[vb trackSpecularColor not]) ifTrue:[specularPart _ aMaterial specularPart]. 1 to: vb vertexCount do:[:i| vtx _ vtxArray at: i. color _ colorArray at: i. "Compute the direction and distance of light source from vertex" direction _ self computeDirectionTo: vtx. distance _ direction length. (distance = 0.0 or:[distance = 1.0]) ifFalse:[direction /= distance negated]. "Compute the attenuation for the given distance" self isAttenuated ifTrue:[scale _ self computeAttenuationFor: distance] ifFalse:[scale _ 1.0]. "Compute spot light factor" self hasSpot ifTrue:[scale _ scale * (self computeSpotFactor: direction)]. "Compute ambient part" self hasAmbientPart ifTrue:[ vb trackAmbientColor ifTrue:[ambientColor _ vtx b3dColor * lightColor ambientPart]. color += (ambientColor * scale). ]. "Compute the diffuse part of the light" self hasDiffusePart ifTrue:[ "Compute angle from light->vertex to vertex normal" cosAngle _ vtx normal dot: direction. "For one-sided lighting negate cosAngle if necessary" (vb twoSidedLighting not and:[cosAngle < 0.0]) ifTrue:[cosAngle _ 0.0 - cosAngle]. "For two-sided lighting check if cosAngle > 0.0 meaning that it is a front face" cosAngle > 0.0 ifTrue:[ vb trackDiffuseColor ifTrue:[diffusePart _ vtx b3dColor]. color += (diffusePart * lightColor diffusePart * (cosAngle * scale)). ]. ]. "Compute specular part of the light" (self hasSpecularPart and:[aMaterial shininess > 0.0]) ifTrue:[ vb useLocalViewer ifTrue:[specDir _ direction - vtx position safelyNormalized] ifFalse:[specDir _ direction - (0@0@1.0)]. cosAngle _ vtx normal dot: specDir. cosAngle > 0.0 ifTrue:[ "Normalize the angle" cosAngle _ cosAngle / specDir length. "cosAngle should be somewhere between 0 and 1. If not, then the vertex normal was not normalized" cosAngle > 1.0 ifTrue:[ specularFactor _ cosAngle raisedTo: aMaterial shininess. ] ifFalse:[ self flag: #TODO. "Use table lookup later" specularFactor _ cosAngle raisedTo: self shininess. ]. color += (specularPart * lightColor specularPart * specularFactor). ]. ]. self flag: #TODO. "Check specular part" colorArray at: i put: color. ].! !!B3DLightSource methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:17'!direction "If the light is directional, return the NORMALIZED direction of the light" ^B3DVector3 zero! !!B3DLightSource methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:28'!hotSpotDeltaCosine "Return the cosine value of the delta radius of a spot light (the fall off region)" ^self hotSpotMaxCosine - self hotSpotMinCosine! !!B3DLightSource methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:27'!hotSpotMaxCosine "Return the cosine value of the outer radius of a spot light (the unlit region)" ^0.0! !!B3DLightSource methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:26'!hotSpotMinCosine "Return the cosine value of the inner radius of a spot light (the fully lit region)" ^0.0! !!B3DLightSource methodsFor: 'accessing' stamp: 'ar 2/8/1999 16:53'!lightColor ^lightColor! !!B3DLightSource methodsFor: 'accessing' stamp: 'ar 2/8/1999 16:53'!lightColor: aMaterialColor lightColor _ aMaterialColor! !!B3DLightSource methodsFor: 'accessing' stamp: 'ti 3/27/2000 14:21'!spotExponent "Return the exponent to be used for the spot fall off computation" ^1.0! !!B3DLightSource methodsFor: 'testing' stamp: 'ar 2/7/1999 17:22'!hasAmbientPart "Return true if the receiver contains an ambient part in its color" ^true! !!B3DLightSource methodsFor: 'testing' stamp: 'ar 2/15/1999 23:07'!hasDiffusePart "Return true if the receiver contains a diffuse part in its color" ^true! !!B3DLightSource methodsFor: 'testing' stamp: 'ar 2/15/1999 23:07'!hasSpecularPart "Return true if the receiver contains a specular part in its color" ^true! !!B3DLightSource methodsFor: 'testing' stamp: 'ar 2/7/1999 18:52'!hasSpot "Return true if the receiver has a hot spot." ^false! !!B3DLightSource methodsFor: 'testing' stamp: 'ar 2/7/1999 17:27'!isAttenuated "Return true if the receiver contains an attenuation. If so, #computeAttenuationFor: must return the attenuation for the given distance." ^true! !!B3DLightSource methodsFor: 'converting' stamp: 'ar 2/7/1999 06:45'!asPrimitiveLight "Convert the receiver into a B3DPrimitiveLight that can be handled by the shader primitive directly. Light sources that cannot be represented as primitive should return nil. This will result in the callback of #shadeVertexBuffer from the shader." ^nil! !!B3DLightSource methodsFor: 'converting' stamp: 'ar 2/8/1999 01:29'!transformedBy: aTransformer ^self clone! !!B3DLightSource methodsFor: 'private' stamp: 'ar 2/7/1999 16:37'!setColor: aColor lightColor _ B3DMaterialColor new. lightColor ambientPart: aColor. lightColor diffusePart: aColor. lightColor specularPart: aColor.! !!B3DLightSource class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 16:09'!color: aColor ^self new setColor: aColor.! !!B3DMaterial methodsFor: 'initialize' stamp: 'ar 2/16/1999 03:05'!from3DS: aDictionary self ambientPart: (aDictionary at: #ambient ifAbsent:[B3DColor4 r: 0.0 g: 0.0 b: 0.0 a: 1.0]). self diffusePart: (aDictionary at: #diffuse ifAbsent:[B3DColor4 r: 0.0 g: 0.0 b: 0.0 a: 1.0]). self specularPart: (aDictionary at: #specular ifAbsent:[B3DColor4 r: 0.0 g: 0.0 b: 0.0 a: 1.0]). (aDictionary includesKey: #textureName) ifTrue:[^(aDictionary at: #textureName) -> self].! !!B3DMaterial methodsFor: 'accessing' stamp: 'ar 2/8/1999 00:54'!emission ^B3DColor4 r: self emissionRed g: self emissionGreen b: self emissionBlue a: self emissionAlpha! !!B3DMaterial methodsFor: 'accessing' stamp: 'ar 2/8/1999 00:53'!emission: aColor self emissionRed: aColor red. self emissionGreen: aColor green. self emissionBlue: aColor blue. self emissionAlpha: aColor alpha.! !!B3DMaterial methodsFor: 'accessing' stamp: 'ar 2/8/1999 00:58'!shininess ^self floatAt: 17! !!B3DMaterial methodsFor: 'accessing' stamp: 'ar 2/8/1999 00:59'!shininess: aFloat ^self floatAt: 17 put: (aFloat max: 0.0).! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:58'!emissionAlpha ^self floatAt: 16! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:59'!emissionAlpha: aFloat self floatAt: 16 put: aFloat! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:58'!emissionBlue ^self floatAt: 15! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:59'!emissionBlue: aFloat self floatAt: 15 put: aFloat! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:58'!emissionGreen ^self floatAt: 14! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:59'!emissionGreen: aFloat self floatAt: 14 put: aFloat! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:58'!emissionRed ^self floatAt: 13! !!B3DMaterial methodsFor: 'element access' stamp: 'ar 2/8/1999 00:59'!emissionRed: aFloat self floatAt: 13 put: aFloat! !!B3DMaterial class methodsFor: 'instance creation' stamp: 'ar 2/8/1999 01:01'!from3DS: aDictionary ^self new from3DS: aDictionary! !!B3DMaterial class methodsFor: 'instance creation' stamp: 'ar 2/8/1999 01:00'!numElements ^17! !!B3DMaterialColor methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:58'!ambientPart ^B3DColor4 r: self ambientRed g: self ambientGreen b: self ambientBlue a: self ambientAlpha! !!B3DMaterialColor methodsFor: 'accessing' stamp: 'ar 2/6/1999 19:00'!ambientPart: aColor self ambientRed: aColor red. self ambientGreen: aColor green. self ambientBlue: aColor blue. self ambientAlpha: aColor alpha.! !!B3DMaterialColor methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:58'!diffusePart ^B3DColor4 r: self diffuseRed g: self diffuseGreen b: self diffuseBlue a: self diffuseAlpha! !!B3DMaterialColor methodsFor: 'accessing' stamp: 'ar 2/6/1999 19:00'!diffusePart: aColor self diffuseRed: aColor red. self diffuseGreen: aColor green. self diffuseBlue: aColor blue. self diffuseAlpha: aColor alpha.! !!B3DMaterialColor methodsFor: 'accessing' stamp: 'ar 2/6/1999 18:59'!specularPart ^B3DColor4 r: self specularRed g: self specularGreen b: self specularBlue a: self specularAlpha! !!B3DMaterialColor methodsFor: 'accessing' stamp: 'ar 2/6/1999 19:01'!specularPart: aColor self specularRed: aColor red. self specularGreen: aColor green. self specularBlue: aColor blue. self specularAlpha: aColor alpha.! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:01'!ambientAlpha ^self floatAt: 4! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!ambientAlpha: aFloat ^self floatAt: 4 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:01'!ambientBlue ^self floatAt: 3! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!ambientBlue: aFloat ^self floatAt: 3 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:01'!ambientGreen ^self floatAt: 2! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!ambientGreen: aFloat ^self floatAt: 2 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:01'!ambientRed ^self floatAt: 1! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!ambientRed: aFloat ^self floatAt: 1 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!diffuseAlpha ^self floatAt: 8! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!diffuseAlpha: aFloat ^self floatAt: 8 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!diffuseBlue ^self floatAt: 7! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!diffuseBlue: aFloat ^self floatAt: 7 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:01'!diffuseGreen ^self floatAt: 6! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!diffuseGreen: aFloat ^self floatAt: 6 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:01'!diffuseRed ^self floatAt: 5! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!diffuseRed: aFloat ^self floatAt: 5 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!specularAlpha ^self floatAt: 12! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!specularAlpha: aFloat ^self floatAt: 12 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!specularBlue ^self floatAt: 11! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:03'!specularBlue: aFloat ^self floatAt: 11 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!specularGreen ^self floatAt: 10! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:04'!specularGreen: aFloat ^self floatAt: 10 put: aFloat! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:02'!specularRed ^self floatAt: 9! !!B3DMaterialColor methodsFor: 'element access' stamp: 'ar 2/6/1999 19:04'!specularRed: aFloat ^self floatAt: 9 put: aFloat! !!B3DMaterialColor methodsFor: 'private' stamp: 'ar 2/7/1999 18:41'!setColor: aColor self ambientPart: aColor. self diffusePart: aColor. self specularPart: aColor.! !!B3DMaterialColor class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 18:41'!color: aColor ^self new setColor: aColor! !!B3DMaterialColor class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 19:04'!numElements ^12! !I represent a general 4x4 transformation matrix commonly used in computer graphics.!!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/1/1999 21:26'!setBSplineBase "Set the receiver to the BSpline base matrix" "for further information see: Foley, van Dam, Feiner, Hughes 'Computer Graphics: Principles and Practice' Addison-Wesley Publishing Company Second Edition, pp. 505" self a11: -1.0 / 6.0; a12: 3.0 / 6.0; a13: -3.0 / 6.0; a14: 1.0 / 6.0; a21: 3.0 / 6.0; a22: -6.0 / 6.0; a23: 3.0 / 6.0; a24: 0.0 / 6.0; a31: -3.0 / 6.0; a32: 0.0 / 6.0; a33: 3.0 / 6.0; a34: 0.0 / 6.0; a41: 1.0 / 6.0; a42: 4.0 / 6.0; a43: 1.0 / 6.0; a44: 0.0 / 6.0! !!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/1/1999 21:26'!setBetaSplineBaseBias: beta1 tension: beta2 "Set the receiver to the betaSpline base matrix if beta1=1 and beta2=0 then the bSpline base matrix will be returned" "for further information see: Foley, van Dam, Feiner, Hughes 'Computer Graphics: Principles and Practice' Addison-Wesley Publishing Company Second Edition, pp. 505" | b12 b13 delta | b12 := beta1 * beta1. b13 := beta1 * b12. delta := 1.0 / (beta2 + (2.0 * b13) + 4.0 * (b12 + beta1) +2.0). self a11: delta * -2.0 * b13; a12: delta * 2.0 * (beta2 + b13 + b12 + beta1); a13: delta * -2.0 * (beta2 + b12 + beta1 + 1.0); a14: delta * 2.0; a21: delta * 6.0 * b13; a22: delta * -3.0 * (beta2 + (2.0 * (b13 + b12))); a23: delta * 3.0 * (beta2 + (2.0 * b12)); a24: 0.0; a31: delta * -6.0 * b13; a32: delta * 6.0 * (b13 - beta1); a33: delta * 6.0 * beta1; a34: 0.0; a41: delta * 2.0 * b13; a42: delta * (beta2 + 4.0 * (b12 + beta1)); a43: delta * 2.0; a44: 0.0! !!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/1/1999 21:27'!setBezierBase "Set the receiver to the bezier base matrix" "for further information see: Foley, van Dam, Feiner, Hughes 'Computer Graphics: Principles and Practice' Addison-Wesley Publishing Company Second Edition, pp. 505" self a11: -1.0; a12: 3.0; a13: -3.0; a14: 1.0; a21: 3.0; a22: -6.0; a23: 3.0; a24: 0.0; a31: -3.0; a32: 3.0; a33: 0.0; a34: 0.0; a41: 1.0; a42: 0.0; a43: 0.0; a44: 0.0! !!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/1/1999 21:27'!setCardinalBase "Set the receiver to the cardinal spline base matrix - just catmull * 2" "for further information see: Foley, van Dam, Feiner, Hughes 'Computer Graphics: Principles and Practice' Addison-Wesley Publishing Company Second Edition, pp. 505" self a11: -1.0; a12: 3.0; a13: -3.0; a14: 1.0; a21: 2.0; a22: -5.0; a23: 4.0; a24: -1.0; a31: -1.0; a32: 0.0; a33: 1.0; a34: 0.0; a41: 0.0; a42: 2.0; a43: 0.0; a44: 0.0! !!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/1/1999 21:27'!setCatmullBase "Set the receiver to the Catmull-Rom base matrix" "for further information see: Foley, van Dam, Feiner, Hughes 'Computer Graphics: Principles and Practice' Addison-Wesley Publishing Company Second Edition, pp. 505" self a11: -0.5; a12: 1.5; a13: -1.5; a14: 0.5; a21: 1.0; a22: -2.5; a23: 2.0; a24: -0.5; a31: -0.5; a32: 0.0; a33: 0.5; a34: 0.0; a41: 0.0; a42: 1.0; a43: 0.0; a44: 0.0! !!B3DMatrix4x4 methodsFor: 'initialize'!setIdentity "Set the receiver to the identity matrix" self loadFrom: B3DIdentityMatrix! !!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/1/1999 21:27'!setPolylineBase "Set the receiver to the polyline base matrix :)" self a11: 0.0; a12: 0.0; a13: 0.0; a14: 0.0; a21: 0.0; a22: 0.0; a23: 0.0; a24: 0.0; a31: 0.0; a32: -1.0; a33: 1.0; a34: 0.0; a41: 0.0; a42: 1.0; a43: 0.0; a44: 0.0! !!B3DMatrix4x4 methodsFor: 'initialize' stamp: 'ar 2/15/1999 02:55'!setScale: aVector self a11: aVector x; a22: aVector y; a33: aVector z! !!B3DMatrix4x4 methodsFor: 'initialize'!setTranslation: aVector self a14: aVector x; a24: aVector y; a34: aVector z! !!B3DMatrix4x4 methodsFor: 'initialize'!setZero "Set the receiver to the zero matrix" self loadFrom: B3DZeroMatrix! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a11 "Return the element a11" ^self at: 1! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a11: aNumber "Store the element a11" self at: 1 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a12 "Return the element a12" ^self at: 2! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a12: aNumber "Store the element a12" self at: 2 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a13 "Return the element a13" ^self at: 3! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a13: aNumber "Store the element a13" self at: 3 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a14 "Return the element a14" ^self at: 4! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a14: aNumber "Store the element a14" self at: 4 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a21 "Return the element a21" ^self at: 5! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a21: aNumber "Store the element a21" self at: 5 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a22 "Return the element a22" ^self at: 6! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a22: aNumber "Store the element a22" self at: 6 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a23 "Return the element a23" ^self at: 7! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a23: aNumber "Store the element a23" self at: 7 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a24 "Return the element a24" ^self at: 8! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a24: aNumber "Store the element a24" self at: 8 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a31 "Return the element a31" ^self at: 9! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a31: aNumber "Store the element a31" self at: 9 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a32 "Return the element a32" ^self at: 10! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a32: aNumber "Store the element a32" self at: 10 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a33 "Return the element a33" ^self at: 11! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a33: aNumber "Store the element a33" self at: 11 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a34 "Return the element a34" ^self at: 12! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a34: aNumber "Store the element a34" self at: 12 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a41 "Return the element a41" ^self at: 13! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a41: aNumber "Store the element a41" self at: 13 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a42 "Return the element a42" ^self at: 14! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a42: aNumber "Store the element a42" self at: 14 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a43 "Return the element a43" ^self at: 15! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a43: aNumber "Store the element a43" self at: 15 put: aNumber! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:29'!a44 "Return the element a44" ^self at: 16! !!B3DMatrix4x4 methodsFor: 'element-access' stamp: 'ar 2/1/1999 21:28'!a44: aNumber "Store the element a44" self at: 16 put: aNumber! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'jsp 2/25/1999 13:58'!alternateRotation "Return the angular rotation around each axis of the matrix" | cp sp cy sy cr sr vAngles | vAngles _ B3DVector3 new. ((self a13) = 0) ifTrue: [ ((self a33) >= 0) ifTrue: [ vAngles at: 2 put: 0. cr _ (self a11). sr _ (self a12). cp _ (self a33). ] ifFalse: [ vAngles at: 2 put: (Float pi). cr _ (self a11) negated. sr _ (self a12) negated. cp _ (self a33) negated. ] ] ifFalse: [ vAngles at: 2 put: (((self a13) negated) arcTan: (self a33)). cy _ (vAngles at: 3) cos. sy _ (vAngles at: 3) sin. cr _ (cy * (self a11)) + (sy * (self a31)). sr _ (cy* (self a12)) + (sy * (self a32)). cp _ (cy * (self a33)) - (sy * (self a13)). ]. sp _ (self a23). vAngles at: 1 put: (sp arcTan: cp). vAngles at: 3 put: (sr arcTan: cr). vAngles at: 1 put: ((vAngles at: 1) radiansToDegrees). vAngles at: 2 put: ((vAngles at: 2) radiansToDegrees). vAngles at: 3 put: ((vAngles at: 3) radiansToDegrees). ^ vAngles.! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'jsp 2/11/1999 14:09'!at: i at: j ^ self at: ((i - 1) * 4 + j).! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'jsp 2/11/1999 14:09'!at: i at: j put: aValue ^ self at: ((i - 1) * 4 + j) put: aValue.! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'jsp 2/25/1999 13:58'!rotation "Return the angular rotation around each axis of the matrix" | vRow1 vRow2 vRow3 vScale vShear vAngles vRowCross determinate | vRow1 _ self row1. vRow2 _ self row2. vRow3 _ self row3. vScale _ B3DVector3 new. vShear _ B3DVector3 new. vAngles _ B3DVector3 new. vScale at: 1 put: (vRow1 length). vRow1 normalize. vShear at: 1 put: (vRow1 dot: vRow2). vRow2 _ vRow2 + (vRow1 * ((vShear at: 1) negated)). vScale at: 2 put: (vRow2 length). vRow2 normalize. vShear at: 1 put: ((vShear at: 1) / (vScale at: 2)). vShear at: 2 put: (vRow1 dot: vRow3). vRow3 _ vRow3 + (vRow1 * ((vShear at: 2) negated)). vShear at: 3 put: (vRow2 dot: vRow3). vRow3 _ vRow3 + (vRow2 * ((vShear at: 3) negated)). vScale at: 3 put: (vRow3 length). vRow3 normalize. vShear at: 2 put: ((vShear at: 2) / (vScale at: 3)). vShear at: 3 put: ((vShear at: 3) / (vScale at: 3)). vRowCross _ vRow2 cross: vRow3. determinate _ vRow1 dot: vRowCross. (determinate < 0.0) ifTrue: [ vRow1 _ vRow1 negated. vRow2 _ vRow2 negated. vRow3 _ vRow3 negated. vScale _ vScale negated. ]. vAngles at: 2 put: ((vRow1 at: 3) negated) arcSin. (((vAngles at: 2) cos) ~= 0.0) ifTrue: [ vAngles at: 1 put: ((vRow2 at: 3) arcTan: (vRow3 at: 3)). vAngles at: 3 put: ((vRow1 at: 2) arcTan: (vRow1 at: 1)). ] ifFalse: [ vAngles at: 1 put: ((vRow2 at: 1) arcTan: (vRow2 at: 2)). vAngles at: 3 put: 0.0 ]. vAngles at: 1 put: ((vAngles at: 1) radiansToDegrees). vAngles at: 2 put: ((vAngles at: 2) radiansToDegrees). vAngles at: 3 put: ((vAngles at: 3) radiansToDegrees). ^ vAngles.! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'jsp 2/24/1999 09:46'!rotation: aVector | xRot yRot zRot cosPitch sinPitch cosYaw sinYaw cosRoll sinRoll | xRot _ (aVector x) degreesToRadians. yRot _ (aVector y) degreesToRadians. zRot _ (aVector z) degreesToRadians. cosPitch _ xRot cos. sinPitch _ xRot sin. cosYaw _ yRot cos. sinYaw _ yRot sin. cosRoll _ zRot cos. sinRoll _ zRot sin. self a11: (cosRoll*cosYaw). self a12: (sinRoll*cosYaw). self a13: (sinYaw negated). self a21: ((cosRoll*sinYaw*sinPitch) - (sinRoll*cosPitch)). self a22: ((cosRoll*cosPitch) + (sinRoll*sinYaw*sinPitch)). self a23: (cosYaw*sinPitch). self a31: ((cosRoll*sinYaw*cosPitch) + (sinRoll*sinPitch)). self a32: ((sinRoll*sinYaw*cosPitch) - (cosRoll*sinPitch)). self a33: (cosYaw*cosPitch). ^ self.! !!B3DMatrix4x4 methodsFor: 'accessing'!rotation: anAngle around: aVector3 "set up a rotation matrix around the direction aVector3" self loadFrom: (B3DRotation angle: anAngle axis: aVector3) asMatrix4x4! !!B3DMatrix4x4 methodsFor: 'accessing'!rotation: anAngle aroundX: xValue y: yValue z: zValue "set up a rotation matrix around the direction x/y/z" ^self rotation: anAngle around:(B3DVector3 with: xValue with: yValue with: zValue)! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:34'!rotationAroundX: anAngle | rad s c | rad := anAngle degreesToRadians. s := rad sin. c := rad cos. self a22: c. self a23: s negated. self a33: c. self a32: s. ^self! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:34'!rotationAroundY: anAngle | rad s c | rad := anAngle degreesToRadians. s := rad sin. c := rad cos. self a11: c. self a13: s. self a33: c. self a31: s negated. ^self! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:35'!rotationAroundZ: anAngle | rad s c | rad := anAngle degreesToRadians. s := rad sin. c := rad cos. self a11: c. self a12: s negated. self a22: c. self a21: s. ^self! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:35'!scaling: aVector ^self scalingX: aVector x y: aVector y z: aVector z! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:35'!scalingX: xValue y: yValue z: zValue self a11: xValue. self a22: yValue. self a33: zValue. ^self! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 4/16/1999 21:51'!squaredDistanceFrom: aMatrix | sum | sum _ 0.0. 1 to: 4 do:[:i| 1 to: 4 do:[:j| sum _ sum + ((self at: i at: j) - (aMatrix at: i at: j)) squared]]. ^sum! !!B3DMatrix4x4 methodsFor: 'accessing'!translation ^(B3DVector3 x: self a14 y: self a24 z: self a34)! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:36'!translation: aVector ^self translationX: aVector x y: aVector y z: aVector z! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:36'!translationX: xValue y: yValue z: zValue self a14: xValue. self a24: yValue. self a34: zValue. ^self! !!B3DMatrix4x4 methodsFor: 'accessing' stamp: 'jsp 2/25/1999 13:58'!trotation "Return the angular rotation around each axis of the matrix" | cp sp cy sy cr sr vAngles | vAngles _ B3DVector3 new. ((self a13) = 0) ifTrue: [ ((self a33) >= 0) ifTrue: [ vAngles at: 2 put: 0. cr _ (self a11). sr _ (self a12). cp _ (self a33). ] ifFalse: [ vAngles at: 2 put: (Float pi). cr _ (self a11) negated. sr _ (self a12) negated. cp _ (self a33) negated. ] ] ifFalse: [ vAngles at: 2 put: (((self a13) negated) arcTan: (self a33)). cy _ (vAngles at: 3) cos. sy _ (vAngles at: 3) sin. cr _ (cy * (self a11)) + (sy * (self a31)). sr _ (cy* (self a12)) + (sy * (self a32)). cp _ (cy * (self a33)) - (sy * (self a13)). ]. sp _ (self a23). vAngles at: 1 put: (sp arcTan: cp). vAngles at: 3 put: (sr arcTan: cr). vAngles at: 1 put: ((vAngles at: 1) radiansToDegrees). vAngles at: 2 put: ((vAngles at: 2) radiansToDegrees). vAngles at: 3 put: ((vAngles at: 3) radiansToDegrees). ^ vAngles.! !!B3DMatrix4x4 methodsFor: 'arithmetic' stamp: 'ar 2/1/1999 21:39'!+ aB3DMatrix "Optimized for Matrix/Matrix operations" <primitive: 'primitiveFloatArrayAddFloatArray'> ^super + aB3DMatrix! !!B3DMatrix4x4 methodsFor: 'arithmetic' stamp: 'ar 2/1/1999 21:39'!- aB3DMatrix "Optimized for Matrix/Matrix operations" <primitive: 'primitiveFloatArraySubFloatArray'> ^super - aB3DMatrix! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'jsp 2/9/1999 17:22'!composeWith: m2 "Perform a 4x4 matrix multiplication." | c1 c2 c3 c4 m3 | m3 _ B3DMatrix4x4 new. c1 _ ((self a11 * m2 a11) + (self a12 * m2 a21) + (self a13 * m2 a31) + (self a14 * m2 a41)). c2 _ ((self a11 * m2 a12) + (self a12 * m2 a22) + (self a13 * m2 a32) + (self a14 * m2 a42)). c3 _ ((self a11 * m2 a13) + (self a12 * m2 a23) + (self a13 * m2 a33) + (self a14 * m2 a43)). c4 _ ((self a11 * m2 a14) + (self a12 * m2 a24) + (self a13 * m2 a34) + (self a14 * m2 a44)). m3 a11: c1; a12: c2; a13: c3; a14: c4. c1 _ ((self a21 * m2 a11) + (self a22 * m2 a21) + (self a23 * m2 a31) + (self a24 * m2 a41)). c2 _ ((self a21 * m2 a12) + (self a22 * m2 a22) + (self a23 * m2 a32) + (self a24 * m2 a42)). c3 _ ((self a21 * m2 a13) + (self a22 * m2 a23) + (self a23 * m2 a33) + (self a24 * m2 a43)). c4 _ ((self a21 * m2 a14) + (self a22 * m2 a24) + (self a23 * m2 a34) + (self a24 * m2 a44)). m3 a21: c1; a22: c2; a23: c3; a24: c4. c1 _ ((self a31 * m2 a11) + (self a32 * m2 a21) + (self a33 * m2 a31) + (self a34 * m2 a41)). c2 _ ((self a31 * m2 a12) + (self a32 * m2 a22) + (self a33 * m2 a32) + (self a34 * m2 a42)). c3 _ ((self a31 * m2 a13) + (self a32 * m2 a23) + (self a33 * m2 a33) + (self a34 * m2 a43)). c4 _ ((self a31 * m2 a14) + (self a32 * m2 a24) + (self a33 * m2 a34) + (self a34 * m2 a44)). m3 a31: c1; a32: c2; a33: c3; a34: c4. c1 _ ((self a41 * m2 a11) + (self a42 * m2 a21) + (self a43 * m2 a31) + (self a44 * m2 a41)). c2 _ ((self a41 * m2 a12) + (self a42 * m2 a22) + (self a43 * m2 a32) + (self a44 * m2 a42)). c3 _ ((self a41 * m2 a13) + (self a42 * m2 a23) + (self a43 * m2 a33) + (self a44 * m2 a43)). c4 _ ((self a41 * m2 a14) + (self a42 * m2 a24) + (self a43 * m2 a34) + (self a44 * m2 a44)). m3 a41: c1; a42: c2; a43: c3; a44: c4. ^m3! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'ar 2/15/1999 23:56'!composedWithGlobal: aB3DMatrix4x4 | result | result _ self class new. self privateTransformMatrix: aB3DMatrix4x4 with: self into: result. ^result! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'ar 2/15/1999 23:57'!composedWithLocal: aB3DMatrix4x4 | result | result _ self class new. self privateTransformMatrix: self with: aB3DMatrix4x4 into: result. ^result! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'ar 5/21/2000 16:34'!inverseTransformation "Return the inverse matrix of the receiver." ^self clone inplaceHouseHolderInvert.! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'ar 2/15/1999 23:50'!localPointToGlobal: aVector "Multiply aVector (temporarily converted to 4D) with the receiver" | x y z rx ry rz rw | x := aVector x. y := aVector y. z := aVector z. rx := (x * self a11) + (y * self a12) + (z * self a13) + self a14. ry := (x * self a21) + (y * self a22) + (z * self a23) + self a24. rz := (x * self a31) + (y * self a32) + (z * self a33) + self a34. rw := (x * self a41) + (y * self a42) + (z * self a43) + self a44. ^B3DVector3 x:(rx/rw) y: (ry/rw) z: (rz/rw)! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'ar 2/7/1999 06:32'!quickTransformV3ArrayFrom: srcArray to: dstArray "Transform the 3 element vertices from srcArray to dstArray. ASSUMPTION: a41 = a42 = a43 = 0.0 and a44 = 1.0" | a11 a12 a13 a14 a21 a22 a23 a24 a31 a32 a33 a34 x y z index | self flag: #b3dPrimitive. a11 _ self a11. a12 _ self a12. a13 _ self a13. a14 _ self a14. a21 _ self a21. a22 _ self a22. a23 _ self a23. a24 _ self a24. a31 _ self a31. a32 _ self a32. a33 _ self a33. a34 _ self a34. 1 to: srcArray size do:[:i| index _ i-1*3. x _ srcArray floatAt: index+1. y _ srcArray floatAt: index+2. z _ srcArray floatAt: index+3. dstArray floatAt: index+1 put: (a11*x) + (a12*y) + (a13*z) + a14. dstArray floatAt: index+2 put: (a21*x) + (a22*y) + (a23*z) + a24. dstArray floatAt: index+3 put: (a31*x) + (a32*y) + (a33*z) + a34. ]. ^dstArray! !!B3DMatrix4x4 methodsFor: 'transforming' stamp: 'ar 2/1/1999 21:42'!transposed "Return a transposed copy of the receiver" | matrix | matrix := self class new. matrix a11: self a11; a12: self a21; a13: self a31; a14: self a41; a21: self a12; a22: self a22; a23: self a32; a24: self a42; a31: self a13; a32: self a23; a33: self a33; a34: self a43; a41: self a14; a42: self a24; a43: self a34; a44: self a44. ^matrix! !!B3DMatrix4x4 methodsFor: 'double dispatching' stamp: 'ar 2/1/1999 21:49'!printOn: aStream "Print the receiver on aStream" 1 to: 4 do:[:r| 1 to: 4 do:[:c| (self at: r-1*4+c) printOn: aStream. aStream nextPut: Character space]. (r < 4) ifTrue:[aStream nextPut: Character cr]].! !!B3DMatrix4x4 methodsFor: 'double dispatching' stamp: 'ar 2/8/1999 20:11'!productFromMatrix4x4: matrix "Multiply a 4x4 matrix with the receiver." | result | result := self class new. result a11: ((matrix a11 * self a11) + (matrix a12 * self a21) + (matrix a13 * self a31) + (matrix a14 * self a41)). result a12: ((matrix a11 * self a12) + (matrix a12 * self a22) + (matrix a13 * self a32) + (matrix a14 * self a42)). result a13: ((matrix a11 * self a13) + (matrix a12 * self a23) + (matrix a13 * self a33) + (matrix a14 * self a43)). result a14: ((matrix a11 * self a14) + (matrix a12 * self a24) + (matrix a13 * self a34) + (matrix a14 * self a44)). result a21: ((matrix a21 * self a11) + (matrix a22 * self a21) + (matrix a23 * self a31) + (matrix a24 * self a41)). result a22: ((matrix a21 * self a12) + (matrix a22 * self a22) + (matrix a23 * self a32) + (matrix a24 * self a42)). result a23: ((matrix a21 * self a13) + (matrix a22 * self a23) + (matrix a23 * self a33) + (matrix a24 * self a43)). result a24: ((matrix a21 * self a14) + (matrix a22 * self a24) + (matrix a23 * self a34) + (matrix a24 * self a44)). result a31: ((matrix a31 * self a11) + (matrix a32 * self a21) + (matrix a33 * self a31) + (matrix a34 * self a41)). result a32: ((matrix a31 * self a12) + (matrix a32 * self a22) + (matrix a33 * self a32) + (matrix a34 * self a42)). result a33: ((matrix a31 * self a13) + (matrix a32 * self a23) + (matrix a33 * self a33) + (matrix a34 * self a43)). result a34: ((matrix a31 * self a14) + (matrix a32 * self a24) + (matrix a33 * self a34) + (matrix a34 * self a44)). result a41: ((matrix a41 * self a11) + (matrix a42 * self a21) + (matrix a43 * self a31) + (matrix a44 * self a41)). result a42: ((matrix a41 * self a12) + (matrix a42 * self a22) + (matrix a43 * self a32) + (matrix a44 * self a42)). result a43: ((matrix a41 * self a13) + (matrix a42 * self a23) + (matrix a43 * self a33) + (matrix a44 * self a43)). result a44: ((matrix a41 * self a14) + (matrix a42 * self a24) + (matrix a43 * self a34) + (matrix a44 * self a44)). ^result! !!B3DMatrix4x4 methodsFor: 'double dispatching'!productFromVector3: aVector3 "Multiply aVector (temporarily converted to 4D) with the receiver" | x y z rx ry rz rw | x := aVector3 x. y := aVector3 y. z := aVector3 z. rx := (x * self a11) + (y * self a21) + (z * self a31) + self a41. ry := (x * self a12) + (y * self a22) + (z * self a32) + self a42. rz := (x * self a13) + (y * self a23) + (z * self a33) + self a43. rw := (x * self a14) + (y * self a24) + (z * self a34) + self a44. ^B3DVector3 x:(rx/rw) y: (ry/rw) z: (rz/rw)! !!B3DMatrix4x4 methodsFor: 'double dispatching'!productFromVector4: aVector4 "Multiply aVector with the receiver" | x y z w rx ry rz rw | x := aVector4 x. y := aVector4 y. z := aVector4 z. w := aVector4 w. rx := (x * self a11) + (y * self a21) + (z * self a31) + (w * self a41). ry := (x * self a12) + (y * self a22) + (z * self a32) + (w * self a42). rz := (x * self a13) + (y * self a23) + (z * self a33) + (w * self a43). rw := (x * self a14) + (y * self a24) + (z * self a34) + (w * self a44). ^B3DVector4 x:rx y: ry z: rz w: rw! !!B3DMatrix4x4 methodsFor: 'solving' stamp: 'ar 2/1/1999 21:50'!inplaceDecomposeLU "Decompose the receiver in place by using gaussian elimination w/o pivot search" | x | 1 to: 4 do:[:j| "i-th equation (row)" j+1 to: 4 do:[:i| x := (self at: i at: j) / (self at: j at: j). j to: 4 do:[:k| self at: i at: k put: (self at: i at: k) - ((self at: j at: k) * x)]. self at: i at: j put: x]].! !!B3DMatrix4x4 methodsFor: 'solving' stamp: 'ar 5/22/2000 17:13'!inplaceHouseHolderInvert "Solve the linear equation self * aVector = x by using HouseHolder's transformation. Note: This scheme is numerically better than using gaussian elimination even though it takes somewhat longer" | d x sigma beta sum s| <primitive:'b3dInplaceHouseHolderInvert' module:'Squeak3D'> x _ B3DMatrix4x4 identity. d _ B3DMatrix4x4 new. 1 to: 4 do:[:j| sigma := 0.0. j to: 4 do:[:i| sigma := sigma + ((self at: i at: j) squared)]. sigma isZero ifTrue:[^nil]. "matrix is singular" ((self at: j at: j) < 0.0) ifTrue:[ s:= sigma sqrt] ifFalse:[ s:= sigma sqrt negated]. 1 to: 4 do:[:r| d at: j at: r put: s]. beta := 1.0 / ( s * (self at: j at: j) - sigma). self at: j at: j put: ((self at: j at: j) - s). "update remaining columns" j+1 to: 4 do:[:k| sum := 0.0. j to: 4 do:[:i| sum := sum + ((self at: i at: j) * (self at: i at: k))]. sum := sum * beta. j to: 4 do:[:i| self at: i at: k put: ((self at: i at: k) + ((self at: i at: j) * sum))]]. "update vector" 1 to: 4 do:[:r| sum := nil. j to: 4 do:[:i| sum := sum isNil ifTrue:[(x at: i at: r) * (self at: i at: j)] ifFalse:[sum + ((x at: i at: r) * (self at: i at: j))]]. sum := sum * beta. j to: 4 do:[:i| x at: i at: r put:((x at: i at: r) + (sum * (self at: i at: j)))]. ]. ]. "Now calculate result" 1 to: 4 do:[:r| 4 to: 1 by: -1 do:[:i| i+1 to: 4 do:[:j| x at: i at: r put: ((x at: i at: r) - ((x at: j at: r) * (self at: i at: j))) ]. x at: i at: r put: ((x at: i at: r) / (d at: i at: r))]. ]. self loadFrom: x. "Return receiver"! !!B3DMatrix4x4 methodsFor: 'solving'!inplaceHouseHolderTransform: aVector "Solve the linear equation self * aVector = x by using HouseHolder's transformation. Note: This scheme is numerically better than using gaussian elimination even though it takes somewhat longer" | d x sigma beta sum s| x := Array with: aVector x with: aVector y with: aVector z with: aVector w. d := Array new: 4. 1 to: 4 do:[:j| sigma := 0.0. j to: 4 do:[:i| sigma := sigma + ((self at: i at: j) squared)]. sigma isZero ifTrue:[^nil]. "matrix is singular" ((self at: j at: j) < 0.0) ifTrue:[ s:= d at: j put: (sigma sqrt)] ifFalse:[ s:= d at: j put: (sigma sqrt negated)]. beta := 1.0 / ( s * (self at: j at: j) - sigma). self at: j at: j put: ((self at: j at: j) - s). "update remaining columns" j+1 to: 4 do:[:k| sum := 0.0. j to: 4 do:[:i| sum := sum + ((self at: i at: j) * (self at: i at: k))]. sum := sum * beta. j to: 4 do:[:i| self at: i at: k put: ((self at: i at: k) + ((self at: i at: j) * sum))]]. "update vector" sum := nil. j to: 4 do:[:i| sum := sum isNil ifTrue:[(x at: i) * (self at: i at: j)] ifFalse:[sum + ((x at: i) * (self at: i at: j))]]. sum := sum * beta. j to: 4 do:[:i| x at: i put:((x at: i) + (sum * (self at: i at: j)))]. ]. "Now calculate result" 4 to: 1 by: -1 do:[:i| i+1 to: 4 do:[:j| x at: i put: ((x at: i) - ((x at: j) * (self at: i at: j))) ]. x at: i put: ((x at: i) / (d at: i))]. ^B3DVector4 x: (x at: 1) y: (x at: 2) z: (x at: 3) w: (x at: 4)! !!B3DMatrix4x4 methodsFor: 'solving' stamp: 'ar 2/1/1999 21:52'!solve: aVector ^self clone inplaceHouseHolderTransform: aVector "or: ^self clone inplaceDecomposeLU solveLU: aVector "! !!B3DMatrix4x4 methodsFor: 'solving'!solveLU: aVector "Given a decomposed matrix using gaussian elimination solve the linear equations." | x v | v := Array with: aVector x with: aVector y with: aVector z with: aVector w. "L first" 1 to: 4 do:[:i| "Top to bottom" x := 0.0. 1 to: i-1 do:[:j| "From left to right w/o diagonal element" x := x + ((v at: j) * (self at: i at: j))]. "No need to divide by the diagonal element - this is always 1.0 in L" v at: i put: (v at: i) - x]. "Now U" 4 to: 1 by: -1 do:[:i| "Bottom to top" x := 0.0. 4 to: i+1 by: -1 do:[:j| "From right to left w/o diagonal element" x := x + ((v at: j) * (self at: i at: j))]. "Divide by diagonal element" v at: i put: (v at: i) - x / (self at: i at: i)]. ^B3DVector4 x: (v at: 1) y: (v at: 2) z: (v at: 3) w: (v at: 4)! !!B3DMatrix4x4 methodsFor: 'comparing' stamp: 'ar 2/1/1999 21:53'!squaredErrorDistanceTo: anotherMatrix | result temp | result := self - anotherMatrix. temp := 0. 1 to: 4 do: [:i | 1 to: 4 do: [:j| temp := temp + ((result at: i-1*4+j) squared)]]. ^temp sqrt.! !!B3DMatrix4x4 methodsFor: 'testing' stamp: 'ar 2/1/1999 21:54'!isIdentity ^self = B3DIdentityMatrix! !!B3DMatrix4x4 methodsFor: 'testing' stamp: 'ar 2/1/1999 21:54'!isZero ^self = B3DZeroMatrix! !!B3DMatrix4x4 methodsFor: 'converting'!asMatrix4x4 ^self! !!B3DMatrix4x4 methodsFor: 'converting' stamp: 'jsp 3/5/1999 15:31'!asQuaternion "Convert the matrix to a quaternion" | x y z a a2 x2 y2 a4 | a2 _ 0.25 * (1.0 + (self a11) + (self a22) + (self a33)). (a2 > 0) ifTrue: [ a _ a2 sqrt. a4 _ 4.0 * a. x _ ((self a32) - (self a23)) / a4. y _ ((self a13) - (self a31)) / a4. z _ ((self a21) - (self a12)) / a4. ] ifFalse: [ a _ 0. x2 _ -0.5 * ((self a22) + (self a33)). (x2 > 0) ifTrue: [ x _ x2 sqrt. x2 _ 2 * x. y _ (self a21) / x2. z _ (self a31) / x2. ] ifFalse: [ x _ 0. y2 _ 0.5 * (1.0 - (self a33)). (y2 > 0) ifTrue: [ y _ y2 sqrt. y2 _ 2 * y. z _ (self a32) / y2. ] ifFalse: [ y _ 0.0. z _ 1.0. ] ] ]. ^ (B3DRotation a: a b: x c: y d: z).! !!B3DMatrix4x4 methodsFor: 'private' stamp: 'ar 2/17/1999 04:23'!privateTransformMatrix: m1 with: m2 into: m3 "Perform a 4x4 matrix multiplication m2 * m1 = m3 being equal to first transforming points by m2 and then by m1. Note that m1 may be identical to m3. NOTE: The primitive implementation does NOT return m3 - and so don't we!!" | c1 c2 c3 c4 | m2 == m3 ifTrue:[^self error:'Argument and result matrix identical']. c1 _ ((m1 a11 * m2 a11) + (m1 a12 * m2 a21) + (m1 a13 * m2 a31) + (m1 a14 * m2 a41)). c2 _ ((m1 a11 * m2 a12) + (m1 a12 * m2 a22) + (m1 a13 * m2 a32) + (m1 a14 * m2 a42)). c3 _ ((m1 a11 * m2 a13) + (m1 a12 * m2 a23) + (m1 a13 * m2 a33) + (m1 a14 * m2 a43)). c4 _ ((m1 a11 * m2 a14) + (m1 a12 * m2 a24) + (m1 a13 * m2 a34) + (m1 a14 * m2 a44)). m3 a11: c1; a12: c2; a13: c3; a14: c4. c1 _ ((m1 a21 * m2 a11) + (m1 a22 * m2 a21) + (m1 a23 * m2 a31) + (m1 a24 * m2 a41)). c2 _ ((m1 a21 * m2 a12) + (m1 a22 * m2 a22) + (m1 a23 * m2 a32) + (m1 a24 * m2 a42)). c3 _ ((m1 a21 * m2 a13) + (m1 a22 * m2 a23) + (m1 a23 * m2 a33) + (m1 a24 * m2 a43)). c4 _ ((m1 a21 * m2 a14) + (m1 a22 * m2 a24) + (m1 a23 * m2 a34) + (m1 a24 * m2 a44)). m3 a21: c1; a22: c2; a23: c3; a24: c4. c1 _ ((m1 a31 * m2 a11) + (m1 a32 * m2 a21) + (m1 a33 * m2 a31) + (m1 a34 * m2 a41)). c2 _ ((m1 a31 * m2 a12) + (m1 a32 * m2 a22) + (m1 a33 * m2 a32) + (m1 a34 * m2 a42)). c3 _ ((m1 a31 * m2 a13) + (m1 a32 * m2 a23) + (m1 a33 * m2 a33) + (m1 a34 * m2 a43)). c4 _ ((m1 a31 * m2 a14) + (m1 a32 * m2 a24) + (m1 a33 * m2 a34) + (m1 a34 * m2 a44)). m3 a31: c1; a32: c2; a33: c3; a34: c4. c1 _ ((m1 a41 * m2 a11) + (m1 a42 * m2 a21) + (m1 a43 * m2 a31) + (m1 a44 * m2 a41)). c2 _ ((m1 a41 * m2 a12) + (m1 a42 * m2 a22) + (m1 a43 * m2 a32) + (m1 a44 * m2 a42)). c3 _ ((m1 a41 * m2 a13) + (m1 a42 * m2 a23) + (m1 a43 * m2 a33) + (m1 a44 * m2 a43)). c4 _ ((m1 a41 * m2 a14) + (m1 a42 * m2 a24) + (m1 a43 * m2 a34) + (m1 a44 * m2 a44)). m3 a41: c1; a42: c2; a43: c3; a44: c4.! !!B3DMatrix4x4 methodsFor: 'row-access' stamp: 'jsp 2/24/1999 17:10'!row1 "Return row 1" ^ (B3DVector3 x: (self a11) y: (self a12) z: (self a13)).! !!B3DMatrix4x4 methodsFor: 'row-access' stamp: 'jsp 2/24/1999 17:11'!row2 "Return row 2" ^ (B3DVector3 x: (self a21) y: (self a22) z: (self a23)).! !!B3DMatrix4x4 methodsFor: 'row-access' stamp: 'jsp 2/24/1999 17:11'!row3 "Return row 3" ^ (B3DVector3 x: (self a31) y: (self a32) z: (self a33)).! !!B3DMatrix4x4 class methodsFor: 'class initialization' stamp: 'ar 2/1/1999 21:58'!initialize "B3DMatrix4x4 initialize" B3DZeroMatrix _ self new. B3DIdentityMatrix _ self new. B3DIdentityMatrix a11: 1.0; a22: 1.0; a33: 1.0; a44: 1.0.! !!B3DMatrix4x4 class methodsFor: 'instance creation'!identity ^self new setIdentity! !!B3DMatrix4x4 class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:25'!numElements ^16! !!B3DMatrix4x4 class methodsFor: 'instance creation' stamp: 'ar 2/15/1999 23:58'!rotatedBy: angle around: axis centeredAt: origin "Create a matrix rotating points around the given origin using the angle/axis pair" | xform | xform _ self withOffset: origin negated. xform _ xform composedWithGlobal:(B3DRotation angle: angle axis: axis) asMatrix4x4. xform _ xform composedWithGlobal: (self withOffset: origin). ^xform! !!B3DMatrix4x4 class methodsFor: 'instance creation' stamp: 'ar 2/15/1999 23:48'!withOffset: amount ^self identity setTranslation: amount! !!B3DMatrix4x4 class methodsFor: 'instance creation'!zero ^self new! !!B3DMorph methodsFor: 'initialize' stamp: 'mjg 9/28/1999 10:19'!initialize super initialize. geometry _ B3DBox from: (-0.7@-0.7@-0.7) to: (0.7@0.7@0.7). camera _ B3DCamera new. (self confirm:'Put me into a clipping frame?') ifTrue:[camera position: 0@0@1.5] ifFalse:[camera position: 0@0@2. color _ nil]. camera nearDistance: 0.1. camera farDistance: 5.0. self extent: 100@100. texture _ (Form extent: 100@100) asTexture. angle _ 0.! !!B3DMorph methodsFor: 'drawing' stamp: 'ar 2/8/1999 02:48'!drawOn: aCanvas color ifNotNil:["aCanvas frameAndFillRectangle: self bounds fillColor: color borderWidth: 1 borderColor: Color black." aCanvas frameRectangle: self bounds color: self color]. aCanvas asBalloonCanvas render: self.! !!B3DMorph methodsFor: 'drawing' stamp: 'ar 2/16/1999 17:26'!renderOn: aRenderer camera ifNotNil:[ aRenderer viewport: (self bounds insetBy: 1@1). aRenderer clearDepthBuffer. aRenderer loadIdentity. camera renderOn: aRenderer]. aRenderer texture: texture. aRenderer transformBy: (B3DRotation angle: angle axis: 0@1@0). geometry ifNotNil:[geometry renderOn: aRenderer].! !!B3DMorph methodsFor: 'stepping' stamp: 'ar 2/4/1999 20:15'!step angle _ angle + 5. self changed.! !!B3DMorph methodsFor: 'stepping' stamp: 'ar 2/4/1999 20:15'!stepTime ^50! !!B3DMorph methodsFor: 'stepping' stamp: 'ar 2/4/1999 20:15'!wantsSteps ^true! !!B3DMorph methodsFor: 'menu' stamp: 'ar 2/16/1999 17:22'!addCustomMenuItems: aCustomMenu hand: aHandMorph super addCustomMenuItems: aCustomMenu hand: aHandMorph. aCustomMenu add:'set texture' action: #setTexture.! !!B3DMorph methodsFor: 'menu' stamp: 'ar 2/16/1999 17:28'!setTexture | tex | tex _ B3DTexture fromDisplay:(Rectangle originFromUser: 128@128). tex wrap: true. tex interpolate: false. tex envMode: 0. texture _ tex. self changed! !The only purpose of this rasterizer is to measure the actual transform/lighting/clipping speed of an engine.!!B3DNullRasterizer methodsFor: 'testing' stamp: 'ar 2/16/1999 02:31'!needsClip "Yepp. We want to see how well our clipper performs." ^true! !!B3DNullRasterizer methodsFor: 'processing' stamp: 'ar 5/26/2000 15:34'!clearViewport: aColor "Do nothing"! !!B3DNullRasterizer class methodsFor: 'testing' stamp: 'ar 2/16/1999 17:37'!isAvailable "Return true if this part of the engine is available" ^true! !!B3DPickerEngine methodsFor: 'initialize' stamp: 'ar 4/18/1999 00:21'!flush "Ignored"! !!B3DPickerEngine methodsFor: 'initialize' stamp: 'ar 6/2/1999 12:08'!initialize "Do not call super initialize here. We get our components directly by the creating engine." pickList _ SortedCollection new: 100. pickList sortBlock:[:a1 :a2| a1 value rasterPosZ < a2 value rasterPosZ]. objects _ OrderedCollection new: 100. objects resetTo: 1. maxVtx _ B3DPrimitiveVertex new. maxVtx rasterPosZ: 1.0e30. maxVtx rasterPosW: 1.0.! !!B3DPickerEngine methodsFor: 'initialize' stamp: 'ar 4/17/1999 23:11'!loadFrom: aRenderEngine "Load our components from the given render engine. The idea is that all of the state is shared so that transformations send during picking will be preserved in the given render engine." vertexBuffer _ aRenderEngine getVertexBuffer. transformer _ aRenderEngine getTransformer. shader _ aRenderEngine getShader. clipper _ aRenderEngine getClipper. rasterizer _ aRenderEngine getRasterizer. ! !!B3DPickerEngine methodsFor: 'picking' stamp: 'ar 4/18/1999 02:25'!pickAt: aPoint extent: extentPoint "Initialize the receiver for picking at the given point using the given extent." pickMatrix _ self pickingMatrixAt: aPoint extent: extentPoint.! !!B3DPickerEngine methodsFor: 'picking' stamp: 'ar 6/2/1999 12:03'!render: anObject | assoc | assoc _ Association key: anObject value: maxVtx. objects addLast: assoc. anObject renderOn: self. (objects removeLast == assoc) ifFalse:[^self error:'Object stack is confused']. assoc value rasterPosZ > 2.0 ifFalse:[pickList add: assoc].! !!B3DPickerEngine methodsFor: 'picking' stamp: 'ar 4/18/1999 00:08'!topMostObject "Return the top most of all picked objects" ^pickList isEmpty ifTrue:[nil] ifFalse:[pickList first key]! !!B3DPickerEngine methodsFor: 'picking' stamp: 'ar 6/2/1999 12:08'!topMostVertex "Return the top most primitive vertex of all picked objects. Note: Except from the z value the vertex is *not* normalized yet (e.g., there was no division by w)" ^pickList isEmpty ifTrue:[nil] ifFalse:[pickList first value]! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 6/2/1999 11:54'!primComputeMinIndexZ: primType vtxArray: vtxArray vtxSize: vtxSize idxArray: idxArray idxSize: idxSize "<primitive: 'b3dComputeMinIndexZ' module: 'Squeak3D'>" ^nil "Indicates failure"! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 03:01'!primComputeMinZ: primType vtxArray: vtxArray vtxSize: vtxSize idxArray: idxArray idxSize: idxSize <primitive: 'b3dComputeMinZ' module: 'Squeak3D'> ^nil "Indicates failure"! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 02:26'!privateTransformVB: vb "Transform the contents of the vertex buffer. Transforming may include normals (if lighting enabled) and textures (if textures enabled)." ^transformer processVertexBuffer: vb modelView: transformer modelViewMatrix projection: (transformer projectionMatrix composedWithGlobal: pickMatrix)! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 6/4/1999 10:28'!processIndexed: vb | idxArray vtxArray index vtx zValue minIndex minZ wValue | idxArray _ vb indexArray. vtxArray _ vb vertexArray. minZ _ 10.0. minIndex _ 0. 1 to: vb indexCount do:[:i| index _ idxArray at: i. index = 0 ifFalse:[ vtx _ vtxArray at: index. zValue _ vtx rasterPosZ. wValue _ vtx rasterPosW. wValue = 0.0 ifFalse:[zValue _ zValue / wValue]. (minIndex = 0 or:[zValue < minZ]) ifTrue:[ minIndex _ index. minZ _ zValue]. ]. ]. ^minIndex! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:42'!processIndexedLines: vb ^self processIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:41'!processIndexedQuads: vb ^self processIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:41'!processIndexedTriangles: vb ^self processIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:43'!processLineLoop: vb ^self processNonIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:43'!processLines: vb ^self processNonIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 6/2/1999 11:54'!processNonIndexed: vb | vtxArray vtx zValue minZ minIndex wValue | vtxArray _ vb vertexArray. minZ _ 10.0. minIndex _ 0. 1 to: vb vertexCount do:[:i| vtx _ vtxArray at: i. zValue _ vtx rasterPosZ. wValue _ vtx rasterPosW. wValue = 0.0 ifFalse:[zValue _ zValue / wValue]. (minIndex = 0 or:[zValue < minZ]) ifTrue:[ minIndex _ i. minZ _ zValue]. ]. ^minIndex! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:44'!processPoints: vb ^self processNonIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 4/18/1999 00:43'!processPolygon: vb ^self processNonIndexed: vb! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 6/4/1999 10:28'!processVertexBuffer: vb | minIndex minVertex minW | minIndex _ self primComputeMinIndexZ: vb primitive vtxArray: vb vertexArray vtxSize: vb vertexCount idxArray: vb indexArray idxSize: vb indexCount. minIndex == nil ifTrue:[minIndex _ super processVertexBuffer: vb]. minIndex = 0 ifTrue:[^maxVtx]. minVertex _ vb vertexArray at: minIndex. minW _ minVertex rasterPosW. minW = 0.0 ifFalse:[minVertex rasterPosZ: minVertex rasterPosZ / minW]. ^minVertex! !!B3DPickerEngine methodsFor: 'private-rendering' stamp: 'ar 11/7/1999 18:12'!renderPrimitive "This is the main rendering loop for all operations" | visible minVertex | "Step 1: Check if the mesh is visible at all" visible _ self privateVisibleVB: vertexBuffer. visible == false ifTrue:[^nil]. "Step 2: Transform vertices, normals, texture coords of the mesh" self privateTransformVB: vertexBuffer. "Step 3: Clip the mesh if necessary" visible _ self privateClipVB: vertexBuffer. visible == false ifTrue:[^nil]. "Step 4: Collect the minimal/maximal distances for the current object." minVertex _ self processVertexBuffer: vertexBuffer. objects isEmpty ifFalse:[ objects last value rasterPosZ > minVertex rasterPosZ ifTrue:[objects last value: minVertex]. ]. ^nil! !!B3DPickerPlugin methodsFor: 'primitives' stamp: 'ar 6/2/1999 11:59'!b3dComputeMinIndexZ "Primitive. Compute and return the index for the minimal z value of all objects in the vertex buffer." | idxSize vtxSize primType vtxArray idxArray minIndex | self export: true. self inline: false. self var: #vtxArray declareC:'float *vtxArray'. self var: #idxArray declareC:'int *idxArray'. interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. idxSize _ interpreterProxy stackIntegerValue: 0. vtxSize _ interpreterProxy stackIntegerValue: 2. primType _ interpreterProxy stackIntegerValue: 4. interpreterProxy failed ifTrue:[^nil]. vtxArray _ self stackPrimitiveVertexArray: 3 ofSize: vtxSize. idxArray _ self stackPrimitiveIndexArray: 1 ofSize: idxSize validate: true forVertexSize: vtxSize. (vtxArray == nil or:[idxArray == nil or:[interpreterProxy failed]]) ifTrue:[^interpreterProxy primitiveFail]. (primType < 1 or:[primType > 6]) ifTrue:[^interpreterProxy primitiveFail]. primType <= 3 ifTrue:[ minIndex _ self processNonIndexedIDX: vtxArray ofSize: vtxSize. ] ifFalse:[ minIndex _ self processIndexedIDX: vtxArray ofSize: vtxSize idxArray: idxArray idxSize: idxSize. ]. interpreterProxy failed ifFalse:[ interpreterProxy pop: 6. "nArgs+rcvr" interpreterProxy pushInteger: minIndex. ].! !!B3DPickerPlugin methodsFor: 'primitives' stamp: 'ar 4/18/1999 02:59'!b3dComputeMinZ "Primitive. Compute and return the minimal z value of all objects in the vertex buffer." | idxSize vtxSize primType vtxArray idxArray minZ | self export: true. self inline: false. self var: #vtxArray declareC:'float *vtxArray'. self var: #idxArray declareC:'int *idxArray'. self var: #minZ declareC:'double minZ'. interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. idxSize _ interpreterProxy stackIntegerValue: 0. vtxSize _ interpreterProxy stackIntegerValue: 2. primType _ interpreterProxy stackIntegerValue: 4. interpreterProxy failed ifTrue:[^nil]. vtxArray _ self stackPrimitiveVertexArray: 3 ofSize: vtxSize. idxArray _ self stackPrimitiveIndexArray: 1 ofSize: idxSize validate: true forVertexSize: vtxSize. (vtxArray == nil or:[idxArray == nil or:[interpreterProxy failed]]) ifTrue:[^interpreterProxy primitiveFail]. (primType < 1 or:[primType > 6]) ifTrue:[^interpreterProxy primitiveFail]. primType <= 3 ifTrue:[ minZ _ self processNonIndexed: vtxArray ofSize: vtxSize. ] ifFalse:[ minZ _ self processIndexed: vtxArray ofSize: vtxSize idxArray: idxArray idxSize: idxSize. ]. interpreterProxy failed ifFalse:[ interpreterProxy pop: 6. "nArgs+rcvr" interpreterProxy pushFloat: minZ. ].! !!B3DPickerPlugin methodsFor: 'processing' stamp: 'ar 4/18/1999 03:05'!processIndexed: vtxArray ofSize: vtxSize idxArray: idxArray idxSize: idxSize | vtxPtr zValue wValue minZ index | self returnTypeC:'double'. self var: #vtxArray declareC:'float *vtxArray'. self var: #vtxPtr declareC:'float *vtxPtr'. self var: #idxArray declareC:'int *idxArray'. self var: #wValue declareC:'double wValue'. self var: #zValue declareC:'double zValue'. self var: #minZ declareC:'double minZ'. minZ _ 10.0. 1 to: idxSize do:[:i| index _ idxArray at: i. index > 0 ifTrue:[ vtxPtr _ vtxArray + (index-1 * PrimVertexSize). zValue _ vtxPtr at: PrimVtxRasterPosZ. wValue _ vtxPtr at: PrimVtxRasterPosW. wValue = 0.0 ifFalse:[zValue _ zValue / wValue]. zValue < minZ ifTrue:[minZ _ zValue]. ]. ]. ^minZ! !!B3DPickerPlugin methodsFor: 'processing' stamp: 'ar 6/2/1999 12:00'!processIndexedIDX: vtxArray ofSize: vtxSize idxArray: idxArray idxSize: idxSize | vtxPtr zValue wValue minZ minIndex index | self var: #vtxArray declareC:'float *vtxArray'. self var: #vtxPtr declareC:'float *vtxPtr'. self var: #idxArray declareC:'int *idxArray'. self var: #wValue declareC:'double wValue'. self var: #zValue declareC:'double zValue'. self var: #minZ declareC:'double minZ'. minZ _ 10.0. minIndex _ 0. 1 to: idxSize do:[:i| index _ idxArray at: i. index > 0 ifTrue:[ vtxPtr _ vtxArray + (index-1 * PrimVertexSize). zValue _ vtxPtr at: PrimVtxRasterPosZ. wValue _ vtxPtr at: PrimVtxRasterPosW. wValue = 0.0 ifFalse:[zValue _ zValue / wValue]. (minIndex = 0 or:[zValue < minZ]) ifTrue:[ minIndex _ i. minZ _ zValue]. ]. ]. ^minIndex! !!B3DPickerPlugin methodsFor: 'processing' stamp: 'ar 4/18/1999 02:49'!processNonIndexed: vtxArray ofSize: vtxSize | vtxPtr zValue wValue minZ | self returnTypeC:'double'. self var: #vtxArray declareC:'float *vtxArray'. self var: #vtxPtr declareC:'float *vtxPtr'. self var: #wValue declareC:'double wValue'. self var: #zValue declareC:'double zValue'. self var: #minZ declareC:'double minZ'. minZ _ 10.0. vtxPtr _ vtxArray. 1 to: vtxSize do:[:i| zValue _ vtxPtr at: PrimVtxRasterPosZ. wValue _ vtxPtr at: PrimVtxRasterPosW. wValue = 0.0 ifFalse:[zValue _ zValue / wValue]. zValue < minZ ifTrue:[minZ _ zValue]. ]. ^minZ! !!B3DPickerPlugin methodsFor: 'processing' stamp: 'ar 6/2/1999 12:00'!processNonIndexedIDX: vtxArray ofSize: vtxSize | vtxPtr zValue wValue minZ minIndex | self var: #vtxArray declareC:'float *vtxArray'. self var: #vtxPtr declareC:'float *vtxPtr'. self var: #wValue declareC:'double wValue'. self var: #zValue declareC:'double zValue'. self var: #minZ declareC:'double minZ'. minZ _ 10.0. minIndex _ 0. vtxPtr _ vtxArray. 1 to: vtxSize do:[:i| zValue _ vtxPtr at: PrimVtxRasterPosZ. wValue _ vtxPtr at: PrimVtxRasterPosW. wValue = 0.0 ifFalse:[zValue _ zValue / wValue]. (minIndex = 0 or:[zValue < minZ]) ifTrue:[ minIndex _ i. minZ _ zValue]. ]. ^minIndex! !This class is used to define the pool dictionary B3DConstants.!!B3DPoolDefiner class methodsFor: 'class initialization' stamp: 'ar 2/8/1999 17:21'!initialize "B3DPoolDefiner initialize" self initPool.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/13/1999 20:30'!defineClipConstants: dict "Initialize the clipper constants" "B3DPoolDefiner initPool" self initFromSpecArray: #( (InLeftBit 16r001) (OutLeftBit 16r002) (InRightBit 16r004) (OutRightBit 16r008) (InTopBit 16r010) (OutTopBit 16r020) (InBottomBit 16r040) (OutBottomBit 16r080) (InFrontBit 16r100) (OutFrontBit 16r200) (InBackBit 16r400) (OutBackBit 16r800) (InAllMask 16r555) (OutAllMask 16rAAA) ) in: dict.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/16/1999 01:22'!defineMaterialAndLights: dict "Initialize constants used for materials and lights" "B3DPoolDefiner initPool" self initFromSpecArray: #( "MaterialColor stuff" (AmbientPart 0) (AmbientRed 0) (AmbientGreen 1) (AmbientBlue 2) (AmbientAlpha 3) (DiffusePart 4) (DiffuseRed 4) (DiffuseGreen 5) (DiffuseBlue 6) (DiffuseAlpha 7) (SpecularPart 8) (SpecularRed 8) (SpecularGreen 9) (SpecularBlue 10) (SpecularAlpha 11) (MaterialColorSize 12) "Size of B3DMaterialColor" "Material definition" (EmissionPart 12) (EmissionRed 12) (EmissionGreen 13) (EmissionBlue 14) (EmissionAlpha 15) (MaterialShininess 16) (MaterialSize 17) "Size of B3DMaterial" "PrimitiveLight definition" (PrimLightPosition 12) (PrimLightPositionX 12) (PrimLightPositionY 13) (PrimLightPositionZ 14) (PrimLightDirection 15) (PrimLightDirectionX 15) (PrimLightDirectionY 16) (PrimLightDirectionZ 17) (PrimLightAttenuation 17) (PrimLightAttenuationConstant 17) (PrimLightAttenuationLinear 18) (PrimLightAttenuationSquared 19) (PrimLightFlags 20) "Spot light stuff" (SpotLightMinCos 21) (SpotLightMaxCos 22) (SpotLightDeltaCos 23) (SpotLightExponent 24) (PrimLightSize 32) "Round up to power of 2" "Primitive light flags" (FlagPositional 16r0001) "Light has an associated position" (FlagDirectional 16r0002) "Light has an associated direction" (FlagAttenuated 16r0004) "Light is attenuated" (FlagHasSpot 16r0008) "Spot values are valid" (FlagAmbientPart 16r0100) "Light has ambient part" (FlagDiffusePart 16r0200) "Light has diffuse part" (FlagSpecularPart 16r0400) "Light has specular part" ) in: dict.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 20:15'!defineMatrixFlags: dict "Define the flags for analyzing vertices" "B3DPoolDefiner initPool" self initFromSpecArray: #( (FlagM44Identity 1) "Matrix is identity" (FlagM44NoPerspective 2) "Matrix has no perspective part" (FlagM44NoTranslation 4) "Matrix has no translation" ) in: dict! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/13/1999 23:41'!definePrimitiveTypes: dict "Initialize the types of Primitives" "B3DPoolDefiner initPool" self initFromSpecArray: #( (PrimTypePoints 1) (PrimTypeLines 2) (PrimTypePolygon 3) (PrimTypeIndexedLines 4) (PrimTypeIndexedTriangles 5) (PrimTypeIndexedQuads 6) (PrimTypeMax 6) "Max used primitive type" ) in: dict.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 4/4/1999 00:46'!definePrimitiveVertexIndexes: dict "Define the indexes for primitive vertices" "B3DPoolDefiner initPool" self initFromSpecArray: #( "Full vertex size is 16 to simplify index computation" (PrimVertexSize 16) "Position" (PrimVtxPosition 0) (PrimVtxPositionX 0) (PrimVtxPositionY 1) (PrimVtxPositionZ 2) "Normal" (PrimVtxNormal 3) (PrimVtxNormalX 3) (PrimVtxNormalY 4) (PrimVtxNormalZ 5) "Tex coord" (PrimVtxTexCoords 6) (PrimVtxTexCoordU 6) (PrimVtxTexCoordV 7) "RasterPos" (PrimVtxRasterPos 8) (PrimVtxRasterPosX 8) (PrimVtxRasterPosY 9) (PrimVtxRasterPosZ 10) (PrimVtxRasterPosW 11) "Color" (PrimVtxColor32 12) "Clip flags" (PrimVtxClipFlags 13) "(Integer) window position" (PrimVtxWindowPosX 14) (PrimVtxWindowPosY 15) ) in: dict! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 17:34'!defineVBConstants: dict "Initialize the vertex buffer constants" "B3DPoolDefiner initPool" self initFromSpecArray: #( "Vertex color tracking flags. These tracks define what part of the material in the shader is determined by the vertex color (if given)." (VBTrackAmbient 1) "ambient part" (VBTrackDiffuse 2) "diffuse part" (VBTrackSpecular 4) "specular part" (VBTrackEmission 8) "emission part -- i.e. simply add vertex color to output" (VBNoTrackMask 4294967280) "Mask out the above flags" "Vertex attribute flags. These flags determine if the primitive vertices include these attributes. Note that color is not included below - it is fully specified by the color tracking flags above." (VBVtxHasNormals 16) "per vertex normals included" (VBVtxHasTexCoords 32) "per vertex tex coords inclueded" "Shader flags stored in the vertex buffer" (VBTwoSidedLighting 64) "Do we shade front and back faces differently?!!" (VBUseLocalViewer 128) "Do we use a local viewer model for specular colors?!!" ) in: dict.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 17:20'!initFromSpecArray: specArray in: aDictionary specArray do:[:spec| self initPoolVariable: spec first value: spec last in: aDictionary. ]! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 17:23'!initPool "B3DPoolDefiner initPool" | poolName | poolName _ self poolName asSymbol. (Smalltalk includesKey: poolName) ifFalse:[ Smalltalk declare: poolName from: Undeclared. ]. (Smalltalk at: poolName) isNil ifTrue:[ (Smalltalk associationAt: poolName) value: Dictionary new. ]. self initPool: (Smalltalk at: poolName).! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/15/1999 04:14'!initPool: aDictionary "B3DPoolDefiner initPool" self defineVBConstants: aDictionary. self definePrimitiveVertexIndexes: aDictionary. self defineMatrixFlags: aDictionary. self defineClipConstants: aDictionary. self definePrimitiveTypes: aDictionary. self defineMaterialAndLights: aDictionary.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 17:23'!initPoolFull "B3DPoolDefiner initPoolFull" "Move old stuff to Undeclared and re-initialize the receiver" | pool | pool _ Smalltalk at: self poolName asSymbol ifAbsent:[Dictionary new]. pool associationsDo:[:assoc| Undeclared declare: assoc key from: pool. ]. self initPool. Undeclared removeUnreferencedKeys.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 17:20'!initPoolVariable: token value: value in: aDictionary aDictionary declare: token from: Undeclared. (aDictionary associationAt: token) value: value.! !!B3DPoolDefiner class methodsFor: 'pool definition' stamp: 'ar 2/8/1999 17:22'!poolName ^#B3DEngineConstants! !!B3DPositionalLight methodsFor: 'initialize' stamp: 'ar 2/7/1999 19:14'!from3DS: aDictionary "Initialize the receiver from a 3DS point light" | color | position _ aDictionary at: #position. color _ aDictionary at: #color. lightColor _ B3DMaterialColor color: color. attenuation _ B3DLightAttenuation constant: 1.0 linear: 0.0 squared: 0.0.! !!B3DPositionalLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:05'!attenuation ^attenuation! !!B3DPositionalLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:05'!attenuation: aLightAttenuation attenuation _ aLightAttenuation! !!B3DPositionalLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:04'!position ^position! !!B3DPositionalLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:04'!position: aVector position _ aVector! !!B3DPositionalLight methodsFor: 'shading' stamp: 'ar 2/7/1999 16:54'!computeAttenuationFor: distance "Compute the attenuation for the given distance" ^attenuation computeAttenuationFor: distance! !!B3DPositionalLight methodsFor: 'shading' stamp: 'ar 2/8/1999 02:01'!computeDirectionTo: aB3DPrimitiveVertex "Compute the lights direction to the given vertex" ^aB3DPrimitiveVertex position - position! !!B3DPositionalLight methodsFor: 'converting' stamp: 'ar 2/15/1999 21:58'!asPrimitiveLight "Convert the receiver into a B3DPrimitiveLight" | primLight flags | primLight _ B3DPrimitiveLight new. primLight position: position. flags _ FlagPositional. self attenuation isIdentity not ifTrue:[ primLight attenuation: self attenuation. flags _ flags bitOr: FlagAttenuated]. lightColor ambientPart isZero ifFalse:[ primLight ambientPart: lightColor ambientPart. flags _ flags bitOr: FlagAmbientPart]. lightColor diffusePart isZero ifFalse:[ primLight diffusePart: lightColor diffusePart. flags _ flags bitOr: FlagDiffusePart]. lightColor specularPart isZero ifFalse:[ primLight specularPart: lightColor specularPart. flags _ flags bitOr: FlagSpecularPart]. primLight flags: flags. ^primLight! !!B3DPositionalLight methodsFor: 'converting' stamp: 'ar 2/8/1999 01:29'!transformedBy: aTransformer ^(super transformedBy: aTransformer) position: (aTransformer transformPosition: position)! !!B3DPositionalLight class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 23:42'!from3DS: aDictionary ^self new from3DS: aDictionary! !!B3DPrimitiveClipper methodsFor: 'clip flags' stamp: 'ar 4/18/1999 02:05'!determineClipFlags: vtxArray count: vtxCount <primitive: 'b3dDetermineClipFlags' module:'Squeak3D'> ^super determineClipFlags: vtxArray count: vtxCount! !!B3DPrimitiveClipper methodsFor: 'clipping polygons' stamp: 'ar 4/18/1999 02:08'!clipPolygon: vtxArray count: vtxCount with: tempVtxArray mask: outMask <primitive:'b3dClipPolygon' module:'Squeak3D'> ^super clipPolygon: vtxArray count: vtxCount with: tempVtxArray mask: outMask! !!B3DPrimitiveClipper methodsFor: 'private' stamp: 'ar 4/18/1999 02:07'!primNextClippedTriangleAfter: firstIndex vertices: vtxArray count: vtxCount indexes: idxArray count: idxCount <primitive: 'b3dPrimitiveNextClippedTriangle' module:'Squeak3D'> ^super primNextClippedTriangleAfter: firstIndex vertices: vtxArray count: vtxCount indexes: idxArray count: idxCount! !!B3DPrimitiveEdge methodsFor: 'initialize' stamp: 'ar 4/3/1999 04:25'!from: vtx0 to: vtx1 (vtx0 sortsBefore: vtx1) ifTrue:[v0 _ vtx0. v1 _ vtx1] ifFalse:[v1 _ vtx0. v0 _ vtx1].! !!B3DPrimitiveEdge methodsFor: 'initialize' stamp: 'ar 4/18/1999 08:05'!initializePass1 "Assume: v0 sortsBefore: v1" xValue _ v0 windowPosX. yValue _ v0 windowPosY. zValue _ v0 rasterPosZ. xIncrement _ (v1 windowPosX - v0 windowPosX) // nLines. zIncrement _ (v1 rasterPosZ - v0 rasterPosZ) / nLines.! !!B3DPrimitiveEdge methodsFor: 'initialize' stamp: 'ar 4/4/1999 21:34'!v0: vtx0 v1: vtx1 v0 _ vtx0. v1 _ vtx1. flags _ 0. nLines _ (vtx1 windowPosY bitShift: -12) - (vtx0 windowPosY bitShift: -12).! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/4/1999 02:41'!flags ^flags! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/4/1999 02:41'!flags: aNumber flags _ aNumber! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:33'!leftFace ^leftFace! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:33'!leftFace: aFace leftFace _ aFace! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 03:25'!nLines ^nLines! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 03:25'!nLines: aNumber nLines _ aNumber! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:33'!rightFace ^rightFace! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:33'!rightFace: aFace rightFace _ aFace.! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/4/1999 20:58'!vertex0 ^v0! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/4/1999 20:58'!vertex1 ^v1! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/6/1999 23:21'!xIncrement ^xIncrement! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:48'!xValue ^xValue! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/5/1999 22:25'!xValue: aNumber xValue _ aNumber! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:48'!yValue ^yValue! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:48'!zValue ^zValue! !!B3DPrimitiveEdge methodsFor: 'accessing' stamp: 'ar 4/6/1999 01:23'!zValue: aNumber zValue _ aNumber! !!B3DPrimitiveEdge methodsFor: 'processing' stamp: 'ar 4/5/1999 02:45'!stepToNextLine "Step to the next scan line" xValue _ xValue + xIncrement. yValue _ yValue + 4096. zValue _ zValue + zIncrement.! !!B3DPrimitiveEdge methodsFor: 'printing' stamp: 'ar 4/4/1999 23:35'!printOn: aStream super printOn: aStream. aStream nextPut:$(; print: (v0 windowPos bitShiftPoint:-12); nextPutAll:' - '; print: (v1 windowPos bitShiftPoint: -12); nextPutAll:' nLines = '; print: nLines; nextPut:$).! !!B3DPrimitiveEdgeList methodsFor: 'initialize' stamp: 'ar 4/4/1999 01:38'!initialize array _ Array new: 100. tally _ 0.! !!B3DPrimitiveEdgeList methodsFor: 'initialize' stamp: 'ar 4/4/1999 21:20'!reset 1 to: tally do:[:i| array at: i put: nil]. tally _ 0.! !!B3DPrimitiveEdgeList methodsFor: 'accessing' stamp: 'ar 4/4/1999 21:42'!at: index ^array at: index! !!B3DPrimitiveEdgeList methodsFor: 'accessing' stamp: 'ar 4/4/1999 21:01'!first ^array at: 1! !!B3DPrimitiveEdgeList methodsFor: 'accessing' stamp: 'ar 4/4/1999 21:42'!size ^tally! !!B3DPrimitiveEdgeList methodsFor: 'accessing' stamp: 'ar 4/6/1999 03:58'!xValues ^(array copyFrom: 1 to: tally) collect:[:e| e xValue]! !!B3DPrimitiveEdgeList methodsFor: 'adding' stamp: 'ar 4/4/1999 23:44'!add: edge1 and: edge2 beforeIndex: index tally+1 >= array size ifTrue:[self grow]. tally+2 to: index+2 by: -1 do:[:i|array at: i put: (array at:i-2)]. "array replaceFrom: index+2 to: tally+2 with: array startingAt: index." array at: index put: edge1. array at: index+1 put: edge2. tally _ tally + 2.! !!B3DPrimitiveEdgeList methodsFor: 'adding' stamp: 'ar 4/4/1999 23:45'!add: edge beforeIndex: index tally = array size ifTrue:[self grow]. tally+1 to: index+1 by: -1 do:[:i|array at: i put: (array at:i-1)]. "array replaceFrom: index+1 to: tally+1 with: array startingAt: index." array at: index put: edge. tally _ tally + 1! !!B3DPrimitiveEdgeList methodsFor: 'enumerating' stamp: 'ar 4/5/1999 02:27'!do: aBlock 1 to: tally do:[:i| aBlock value: (array at: i)].! !!B3DPrimitiveEdgeList methodsFor: 'enumerating' stamp: 'ar 4/4/1999 01:39'!xValue: xValue from: firstIndex do: aBlock "Enumerate the entries in the insertion list starting at the given first index. Evaluate aBlock with the entries having the requested x value. Return the index after the last element touched." | edge | firstIndex to: tally do:[:i| edge _ array at: i. edge xValue = xValue ifFalse:[^i]. aBlock value: edge. ]. ^tally+1! !!B3DPrimitiveEdgeList methodsFor: 'testing' stamp: 'ar 4/4/1999 23:09'!isEmpty ^tally = 0! !!B3DPrimitiveEdgeList methodsFor: 'sorting' stamp: 'ar 4/5/1999 01:41'!firstIndexForInserting: xValue "Return the first possible index for inserting an object with the given xValue" | index | index _ self indexForInserting: xValue. [index > 1 and:[(array at: index-1) xValue = xValue]] whileTrue:[index _ index-1]. ^index! !!B3DPrimitiveEdgeList methodsFor: 'sorting' stamp: 'ar 4/5/1999 01:41'!indexForInserting: xValue "Return the appropriate index for inserting the given x value" | index low high | low _ 1. high _ tally. [index _ high + low // 2. low > high] whileFalse:[ (array at: index) xValue <= xValue ifTrue: [low _ index + 1] ifFalse: [high _ index - 1]]. ^low! !!B3DPrimitiveEdgeList methodsFor: 'private' stamp: 'ar 4/4/1999 01:38'!grow | newArray | newArray _ array species new: array size + 100. newArray replaceFrom: 1 to: array size with: array startingAt: 1. array _ newArray.! !!B3DPrimitiveEdgeList class methodsFor: 'instance creation' stamp: 'ar 4/4/1999 04:27'!new ^super new initialize! !I am a basic render engine with some primitive level support for transformation, lighting and (once it is done) clipping.!!B3DPrimitiveEngine class methodsFor: 'accessing' stamp: 'ar 4/16/1999 06:45'!clipper ^B3DPrimitiveClipper "^B3DVertexClipper"! !!B3DPrimitiveEngine class methodsFor: 'accessing' stamp: 'ar 4/12/1999 03:47'!rasterizer "Return the rasterizer to use with this engine" ^B3DPrimitiveRasterizer! !!B3DPrimitiveEngine class methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:24'!shader "Return the shader to use with this engine" ^B3DPrimitiveShader! !!B3DPrimitiveEngine class methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:24'!transformer "Return the transformer to use with this engine" ^B3DPrimitiveTransformer! !!B3DPrimitiveFace methodsFor: 'initialize' stamp: 'ar 4/5/1999 18:29'!initializeDepthBounds "Compute minZ/maxZ" v0 rasterPosZ <= v1 rasterPosZ ifTrue:[ v1 rasterPosZ <= v2 rasterPosZ ifTrue:[minZ _ v0 rasterPosZ. maxZ _ v2 rasterPosZ] ifFalse:[v0 rasterPosZ <= v2 rasterPosZ ifTrue:[minZ _ v0 rasterPosZ. maxZ _ v1 rasterPosZ] ifFalse:[minZ _ v2 rasterPosZ. maxZ _ v1 rasterPosZ]]. ] ifFalse:[ v2 rasterPosZ <= v1 rasterPosZ ifTrue:[minZ _ v2 rasterPosZ. maxZ _ v0 rasterPosZ] ifFalse:[v0 rasterPosZ <= v2 rasterPosZ ifTrue:[minZ _ v1 rasterPosZ. maxZ _ v2 rasterPosZ] ifFalse:[minZ _ v1 rasterPosZ. maxZ _ v0 rasterPosZ]]. ].! !!B3DPrimitiveFace methodsFor: 'initialize' stamp: 'ar 4/8/1999 04:32'!initializePass1 "Assume: v0 sortsBefore: v1 sortsBefore: v2" | area majorDz minorDz | self initializeDepthBounds. "Compute minZ/maxZ" "Compute the major and minor reference edges" majorDx _ v2 rasterPosX - v0 rasterPosX. majorDy _ v2 rasterPosY - v0 rasterPosY. minorDx _ v1 rasterPosX - v0 rasterPosX. minorDy _ v1 rasterPosY - v0 rasterPosY. "Compute the inverse area of the face" area _ (majorDx * minorDy) - (minorDx * majorDy). ((area > -0.001) and:[area < 0.001]) ifTrue:[oneOverArea _ 0.0] ifFalse:[oneOverArea _ 1.0 / area]. "Compute dzdx and dzdy" majorDz _ v2 rasterPosZ - v0 rasterPosZ. minorDz _ v1 rasterPosZ - v0 rasterPosZ. dzdx _ oneOverArea * ((majorDz * minorDy) - (minorDz * majorDy)). dzdy _ oneOverArea * ((majorDx * minorDz) - (majorDz * minorDx)).! !!B3DPrimitiveFace methodsFor: 'initialize' stamp: 'ar 4/18/1999 06:35'!initializePass2 "The receiver is about to be drawn. Initialize all the attributes deferred until now." | majorDv minorDv dvdx dvdy w0 w1 w2 baseValue rAttr gAttr bAttr aAttr wAttr sAttr tAttr | "Red" majorDv _ v2 redValue - v0 redValue. minorDv _ v1 redValue - v0 redValue. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). attributes _ rAttr _ B3DPrimitiveFaceAttributes new. rAttr value: v0 redValue; dvdx: dvdx; dvdy: dvdy. "Green" majorDv _ v2 greenValue - v0 greenValue. minorDv _ v1 greenValue - v0 greenValue. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). gAttr _ B3DPrimitiveFaceAttributes new. gAttr value: v0 greenValue; dvdx: dvdx; dvdy: dvdy. rAttr nextAttr: gAttr. "Blue" majorDv _ v2 blueValue - v0 blueValue. minorDv _ v1 blueValue - v0 blueValue. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). bAttr _ B3DPrimitiveFaceAttributes new. bAttr value: v0 blueValue; dvdx: dvdx; dvdy: dvdy. gAttr nextAttr: bAttr. "Alpha" majorDv _ v2 alphaValue - v0 alphaValue. minorDv _ v1 alphaValue - v0 alphaValue. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). aAttr _ B3DPrimitiveFaceAttributes new. aAttr value: v0 alphaValue; dvdx: dvdx; dvdy: dvdy. bAttr nextAttr: aAttr. "W part" texture == nil ifFalse:[ w0 _ v0 rasterPosW. w1 _ v1 rasterPosW. w2 _ v2 rasterPosW. majorDv _ w2 - w0. minorDv _ w1 - w0. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). wAttr _ B3DPrimitiveFaceAttributes new. wAttr value: w0; dvdx: dvdx; dvdy: dvdy. aAttr nextAttr: wAttr. baseValue _ v0 texCoordS * w0. majorDv _ (v2 texCoordS * w2) - baseValue. minorDv _ (v1 texCoordS * w1) - baseValue. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). sAttr _ B3DPrimitiveFaceAttributes new. sAttr value: baseValue; dvdx: dvdx; dvdy: dvdy. wAttr nextAttr: sAttr. baseValue _ v0 texCoordT * w0. majorDv _ (v2 texCoordT * w2) - baseValue. minorDv _ (v1 texCoordT * w1) - baseValue. dvdx _ oneOverArea * ((majorDv * minorDy) - (minorDv * majorDy)). dvdy _ oneOverArea * ((majorDx * minorDv) - (majorDv * minorDx)). tAttr _ B3DPrimitiveFaceAttributes new. tAttr value: baseValue; dvdx: dvdx; dvdy: dvdy. sAttr nextAttr: tAttr. ].! !!B3DPrimitiveFace methodsFor: 'initialize' stamp: 'ar 4/4/1999 21:54'!v0: vtx0 v1: vtx1 v2: vtx2 v0 _ vtx0. v1 _ vtx1. v2 _ vtx2. flags _ 0.! !!B3DPrimitiveFace methodsFor: 'initialize' stamp: 'ar 4/7/1999 01:01'!validateDepthSetup oneOverArea = 0.0 ifTrue:[^self]. (v0 rasterPosZ - (self zValueAtX: v0 rasterPosX y: v0 rasterPosY)) abs >= 1.0e-10 ifTrue:[self error:'Depth problem']. (v1 rasterPosZ - (self zValueAtX: v1 rasterPosX y: v1 rasterPosY)) abs >= 1.0e-10 ifTrue:[self error:'Depth problem']. (v2 rasterPosZ - (self zValueAtX: v2 rasterPosX y: v2 rasterPosY)) abs >= 1.0e-10 ifTrue:[self error:'Depth problem'].! !!B3DPrimitiveFace methodsFor: 'initialize' stamp: 'ar 4/3/1999 21:24'!validateVertexOrder (v0 sortsBefore: v1) ifFalse:[self error:'Vertex order problem']. (v0 sortsBefore: v2) ifFalse:[self error:'Vertex order problem']. (v1 sortsBefore: v2) ifFalse:[self error:'Vertex order problem'].! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/6/1999 22:40'!attributes ^attributes! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 04:13'!dzdx ^dzdx! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 04:13'!dzdy ^dzdy! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:34'!flags ^flags! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:34'!flags: anInteger flags _ anInteger! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 19:05'!leftEdge ^leftEdge! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 19:06'!leftEdge: anEdge leftEdge _ anEdge! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 18:22'!maxZ ^maxZ! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 18:21'!minZ ^minZ! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:33'!nextFace ^nextFace! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:34'!nextFace: aFace nextFace _ aFace! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 19:03'!oneOverArea ^oneOverArea! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:33'!prevFace ^prevFace! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 00:34'!prevFace: aFace prevFace _ aFace! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 19:05'!rightEdge ^rightEdge! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/5/1999 19:06'!rightEdge: anEdge rightEdge _ anEdge! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:20'!texture ^texture! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:20'!texture: aTexture texture _ aTexture! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 21:32'!vertex0 ^v0! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 21:32'!vertex1 ^v1! !!B3DPrimitiveFace methodsFor: 'accessing' stamp: 'ar 4/3/1999 21:32'!vertex2 ^v2! !!B3DPrimitiveFace methodsFor: 'processing' stamp: 'ar 4/18/1999 06:34'!attrValue: attr atX: xValue y: yValue "Return the value of the attribute at position xValue@yValue" ^attr valueAtX: (xValue - v0 rasterPosX) y: (yValue - v0 rasterPosY).! !!B3DPrimitiveFace methodsFor: 'processing' stamp: 'ar 4/8/1999 04:31'!zValueAtX: xValue y: yValue "Return the z value of the receiver at position xValue@yValue" ^v0 rasterPosZ + (yValue - v0 rasterPosY * dzdy) + (xValue - v0 rasterPosX * dzdx)! !!B3DPrimitiveFace methodsFor: 'printing' stamp: 'ar 4/5/1999 01:22'!printOn: aStream super printOn: aStream. aStream nextPut:$(; print: (v0 windowPos bitShiftPoint:-12); nextPutAll:' - '; print: (v1 windowPos bitShiftPoint: -12); nextPutAll:' - '; print: (v2 windowPos bitShiftPoint: -12); nextPut:$).! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:33'!dvdx ^dvdx! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:33'!dvdx: aNumber dvdx _ aNumber! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:33'!dvdy ^dvdy! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:33'!dvdy: aNumber dvdy _ aNumber! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:32'!nextAttr ^nextAttr! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:32'!nextAttr: attr nextAttr _ attr.! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:32'!value ^value! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:32'!value: aNumber value _ aNumber! !!B3DPrimitiveFaceAttributes methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:34'!valueAtX: xValue y: yValue "Return the value of the attribute at position xValue@yValue" ^value + (yValue * dvdy) + (xValue * dvdx)! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 03:51'!attenuation "Return the light attenuation. This member is only valid if the light is attenuated." ^B3DLightAttenuation constant: self constantAttenuation linear: self linearAttenuation squared: self squaredAttenuation! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 03:52'!attenuation: aLightAttenuation "Set the light attenuation. This member is only valid if the light is attenuated." self constantAttenuation: aLightAttenuation constantPart. self linearAttenuation: aLightAttenuation linearPart. self squaredAttenuation: aLightAttenuation squaredPart.! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 03:47'!direction "Return the direction of the light. This member is valid only if the light is not positional (e.g., the direction must be computed for every vertex)" ^B3DVector3 x: self directionX y: self directionY z: self directionZ! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 03:49'!direction: aB3DVector "Set the direction of the light. This member is valid only if the light is positional (e.g., the direction must be computed for every vertex)" self directionX: aB3DVector x. self directionY: aB3DVector y. self directionZ: aB3DVector z.! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:17'!flags ^self wordAt: PrimLightFlags+1! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:17'!flags: aValue ^self wordAt: PrimLightFlags+1 put: aValue! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 03:49'!position "Return the position of the light. This member is valid only if the light is not positional (e.g., the direction must be computed for every vertex)" ^B3DVector3 x: self positionX y: self positionY z: self positionZ! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 03:48'!position: aB3DVector "Set the position of the light. This member is valid only if the light is positional (e.g., the direction must be computed for every vertex)" self positionX: aB3DVector x. self positionY: aB3DVector y. self positionZ: aB3DVector z.! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:17'!spotDeltaCos ^self floatAt: SpotLightDeltaCos+1! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:17'!spotDeltaCos: aFloat ^self floatAt: SpotLightDeltaCos+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:17'!spotExponent ^self floatAt: SpotLightExponent+1! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:17'!spotExponent: aFloat ^self floatAt: SpotLightExponent+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:18'!spotMaxCos ^self floatAt: SpotLightMaxCos+1! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:18'!spotMaxCos: aFloat ^self floatAt: SpotLightMaxCos+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:18'!spotMinCos ^self floatAt: SpotLightMinCos+1! !!B3DPrimitiveLight methodsFor: 'accessing' stamp: 'ar 2/15/1999 22:18'!spotMinCos: aFloat ^self floatAt: SpotLightMinCos+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:14'!constantAttenuation ^self floatAt: PrimLightAttenuationConstant+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:14'!constantAttenuation: aFloat ^self floatAt: PrimLightAttenuationConstant+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:14'!directionX ^self floatAt: PrimLightDirectionX+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:14'!directionX: aFloat ^self floatAt: PrimLightDirectionX+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:14'!directionY ^self floatAt: PrimLightDirectionY+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!directionY: aFloat ^self floatAt: PrimLightDirectionY+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!directionZ ^self floatAt: PrimLightDirectionZ+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!directionZ: aFloat ^self floatAt: PrimLightDirectionZ+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!linearAttenuation ^self floatAt: PrimLightAttenuationLinear+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!linearAttenuation: aFloat ^self floatAt: PrimLightAttenuationLinear+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!positionX ^self floatAt: PrimLightPositionX+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!positionX: aFloat ^self floatAt: PrimLightPositionX+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!positionY ^self floatAt: PrimLightPositionY+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!positionY: aFloat ^self floatAt: PrimLightPositionY+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!positionZ ^self floatAt: PrimLightPositionZ+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!positionZ: aFloat ^self floatAt: PrimLightPositionZ+1 put: aFloat! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!squaredAttenuation ^self floatAt: PrimLightAttenuationSquared+1! !!B3DPrimitiveLight methodsFor: 'element access' stamp: 'ar 2/15/1999 22:15'!squaredAttenuation: aFloat ^self floatAt: PrimLightAttenuationSquared+1 put: aFloat! !!B3DPrimitiveLight class methodsFor: 'instance creation' stamp: 'ar 2/15/1999 22:11'!numElements ^PrimLightSize! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:43'!bounds ^bounds! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 04:49'!faces ^faces! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 04:49'!faces: anArray faces _ anArray! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:44'!nextObj ^next! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:44'!nextObj: obj next _ obj! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:44'!prevObj ^prev! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:45'!prevObj: obj prev _ obj! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:56'!texture ^texture! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 06:56'!texture: aTexture texture _ aTexture! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 04:49'!vertices ^vertices! !!B3DPrimitiveObject methodsFor: 'accessing' stamp: 'ar 4/18/1999 04:49'!vertices: anArray vertices _ anArray! !!B3DPrimitiveObject methodsFor: 'processing' stamp: 'ar 4/18/1999 05:44'!mapVertices: viewport "Map all the vertices in the receiver" | xOfs yOfs xScale yScale w x y z scaledX scaledY first | xOfs _ (viewport origin x + viewport corner x) * 0.5 - 0.5. yOfs _ (viewport origin y + viewport corner y) * 0.5 - 0.5. xScale _ (viewport corner x - viewport origin x) * 0.5. yScale _ (viewport corner y - viewport origin y) * -0.5. bounds _ 16r3FFFFFFF asPoint extent: 0@0. minZ _ maxZ _ 0.0. first _ true. vertices do:[:vtx| w _ vtx rasterPosW. w = 0.0 ifFalse:[w _ 1.0 / w]. x _ vtx rasterPosX * w * xScale + xOfs. y _ vtx rasterPosY * w * yScale + yOfs. z _ vtx rasterPosZ * w. vtx rasterPosW: w. vtx rasterPosZ: z. scaledX _ (x * 4096.0) asInteger. scaledY _ (y * 4096.0) asInteger. vtx windowPosX: scaledX. vtx windowPosY: scaledY. true ifTrue:[ vtx rasterPosX: scaledX / 4096.0. vtx rasterPosY: scaledY / 4096.0. ] ifFalse:[ vtx rasterPosX: x. vtx rasterPosY: y. ]. first ifTrue:[ bounds _ scaledX@scaledY extent: 0@0. minZ _ maxZ _ z. first _ false. ] ifFalse:[ bounds _ bounds encompass: scaledX@scaledY. minZ _ minZ min: z. maxZ _ maxZ max: z. ]. ]. bounds _ (bounds origin bitShiftPoint: -12) corner: (bounds corner bitShiftPoint: -12).! !!B3DPrimitiveObject methodsFor: 'processing' stamp: 'ar 4/18/1999 05:12'!setupVertexOrder faces do:[:face| self setupVertexOrder: face].! !!B3DPrimitiveObject methodsFor: 'processing' stamp: 'ar 4/18/1999 05:10'!setupVertexOrder: face | p1 p2 i1 i2 i3 p3 | i1 _ face p1Index. i2 _ face p2Index. i3 _ face p3Index. p1 _ vertices at: i1. p2 _ vertices at: i2. p3 _ vertices at: i3. (p1 sortsBefore: p2) ifTrue:[ (p2 sortsBefore: p3) ifTrue:[ face p1Index: i1; p2Index: i2; p3Index: i3. ] ifFalse:[ (p1 sortsBefore: p3) ifTrue:[face p1Index: i1; p2Index: i3; p3Index: i2] ifFalse:[face p1Index: i3; p2Index: i1; p3Index: i2] ]. ] ifFalse:[ (p1 sortsBefore: p3) ifTrue:[ face p1Index: i2; p2Index: i1; p3Index: i3. ] ifFalse:[ (p2 sortsBefore: p3) ifTrue:[face p1Index: i2; p2Index: i3; p3Index: i1] ifFalse:[face p1Index: i3; p2Index: i2; p3Index: i1] ] ]. B3DScanner doDebug ifTrue:[ p1 _ vertices at: face p1Index. p2 _ vertices at: face p2Index. p3 _ vertices at: face p3Index. ((p1 sortsBefore: p2) and:[(p2 sortsBefore: p3) and:[p1 sortsBefore: p3]]) ifFalse:[self error:'Vertex order problem']. ].! !!B3DPrimitiveObject methodsFor: 'processing' stamp: 'ar 4/18/1999 05:13'!sortInitialFaces faces _ faces sortBy:[:face1 :face2| (vertices at: face1 p1Index) sortsBefore: (vertices at: face2 p1Index)].! !!B3DPrimitiveObject methodsFor: 'initialize' stamp: 'ar 4/18/1999 05:22'!reset start _ 0.! !!B3DPrimitiveObject methodsFor: 'streaming' stamp: 'ar 4/18/1999 05:26'!atEnd ^start >= faces size! !!B3DPrimitiveObject methodsFor: 'streaming' stamp: 'ar 4/18/1999 06:55'!next | iFace face | iFace _ faces at: (start _ start + 1). face _ B3DPrimitiveFace new. face v0: (vertices at: iFace p1Index) v1: (vertices at: iFace p2Index) v2: (vertices at: iFace p3Index). face texture: texture. face initializePass1. B3DScanner doDebug ifTrue:[ face validateVertexOrder. face validateDepthSetup]. ^face! !!B3DPrimitiveObject methodsFor: 'streaming' stamp: 'ar 4/18/1999 05:25'!peekY ^(vertices at: (faces at: start+1) p1Index) windowPosY! !!B3DPrimitiveRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:41'!clipRect: aRectangle super clipRect: aRectangle. state bitBlt clipRect: aRectangle.! !!B3DPrimitiveRasterizer methodsFor: 'initialize' stamp: 'ar 4/17/1999 21:10'!flush self mainLoop.! !!B3DPrimitiveRasterizer methodsFor: 'initialize' stamp: 'ar 4/16/1999 07:54'!initialize super initialize. primObjects _ WriteStream on: (Array new: 100). state _ B3DPrimitiveRasterizerState new. state initialize. textures _ IdentityDictionary new: 33.! !!B3DPrimitiveRasterizer methodsFor: 'initialize' stamp: 'ar 4/10/1999 22:53'!reset super reset. state reset.! !!B3DPrimitiveRasterizer methodsFor: 'initialize' stamp: 'ar 5/28/2000 12:16'!target: aForm | bb span sourceForm | super target: aForm. target ifNil:[^self]. "Note: span must be Bitmap since software rasterizer expects canonical RGBA for now" span _ Bitmap new: 2048. sourceForm _ Form extent: span size@1 depth: 32 bits: span. bb _ BitBlt current toForm: target. self class primitiveSetBitBltPlugin: bb getPluginName. bb sourceForm: sourceForm. bb isFXBlt ifTrue:[ "Specific setup for FXBlt is necessary" bb colorMap: (sourceForm colormapIfNeededFor: target). bb combinationRule: (target depth >= 8 ifTrue:[34] ifFalse:[Form paint]). ] ifFalse:[ bb colorMap: (sourceForm colormapIfNeededForDepth: target depth). bb combinationRule: (target depth >= 8 ifTrue:[34] ifFalse:[Form paint]). ]. bb destX: 0; destY: 0; sourceX: 0; sourceY: 0; width: 1; height: 1. state spanBuffer: span. state bitBlt: bb.! !!B3DPrimitiveRasterizer methodsFor: 'testing' stamp: 'ar 4/14/1999 02:08'!needsClip ^true! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 11/7/1999 18:47'!addPrimitiveObject: vb ofSize: objSize | obj textureIndex | texture == nil ifTrue:[textureIndex _ 0] ifFalse:[textureIndex _ textures at: texture ifAbsentPut:[textures size+1]]. obj _ B3DPrimitiveRasterizerData new: objSize. self primAddObject: obj primitive: vb primitive vertexArray: vb vertexArray size: vb vertexCount indexArray: vb indexArray size: vb indexCount viewport: viewport textureIndex: textureIndex. primObjects nextPut: obj. "AAARRRRGGGGGHHHH - we should do this differently!!!!!!!!" vbBounds _ (obj integerAt: 9) @ (obj integerAt: 11) corner: (obj integerAt: 10) @ (obj integerAt: 12).! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 5/26/2000 15:41'!debugDrawVB: vb | vtx idx1 idx2 idx3 v1 v2 v3 vp myCanvas | myCanvas _ target getCanvas. vp _ viewport clone. vtx _ Array new: vb vertexCount. vb vertexArray upTo: vb vertexCount doWithIndex:[:v :i| vtx at: i put: (vp mapVertex4: v rasterPos). ]. 1 to: vb indexCount-1 by: 3 do:[:i| idx1 _ vb indexArray at: i. idx2 _ vb indexArray at: i+1. idx3 _ vb indexArray at: i+2. idx1 = 0 ifFalse:[ v1 _ vtx at: idx1. v2 _ vtx at: idx2. v3 _ vtx at: idx3. myCanvas line: v1 to: v2 width: 1 color: Color black. myCanvas line: v2 to: v3 width: 1 color: Color black. myCanvas line: v3 to: v1 width: 1 color: Color black. ]. ].! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 11/7/1999 22:25'!mainLoop "Do the actual rasterization" | errCode objects textureArray | objects _ primObjects contents. objects size = 0 ifTrue:[^self]. "Nothing to do" textureArray _ Array new: textures size. textures associationsDo:[:assoc| textureArray at: assoc value put: assoc key]. state initObjects: objects size. state initTextures: textureArray size. textureArray do:[:tex| tex unhibernate]. [errCode _ self primStartRasterizer: state objects: objects textures: textureArray. errCode = 0] whileFalse:[ "Not yet finished" self processErrorCode: (errCode bitAnd: 255). state reset]. primObjects reset. textures _ IdentityDictionary new: textures capacity. false ifTrue:[self printSpaceUsage: objects].! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 4/12/1999 02:32'!processErrorCode: errCode errCode = 0 ifTrue:[^true]. "This is allowed!!" (errCode = B3DNoMoreEdges) ifTrue:[^state growEdges]. (errCode = B3DNoMoreFaces) ifTrue:[^state growFaces]. (errCode = B3DNoMoreAttrs) ifTrue:[^state growAttrs]. (errCode = B3DNoMoreAET) ifTrue:[^state growAET]. (errCode = B3DNoMoreAdded) ifTrue:[^state growAdded]. self error:'Unknown rasterizer error code ', errCode printString.! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 4/17/1999 20:29'!processIndexedLines: vb "Process an indexed line set" self error:'Indexed lines are not yet implemented'! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 9/10/1999 14:58'!processIndexedQuads: vb "Process an indexed quad set" | objSize | objSize _ self primObjectSize + (vb vertexCount + 1 * PrimVertexSize) + (vb indexCount). self addPrimitiveObject: vb ofSize: objSize.! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 9/10/1999 14:59'!processIndexedTriangles: vb | objSize | objSize _ self primObjectSize + (vb vertexCount + 1 * PrimVertexSize) + (vb indexCount). self addPrimitiveObject: vb ofSize: objSize.! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 4/17/1999 20:29'!processLineLoop: vb "Process a closed line defined by the vertex buffer" self error:'Lines are not yet implemented'! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 4/17/1999 20:29'!processLines: vb "Process a series of lines defined by each two points the vertex buffer" self error:'Lines are not yet implemented'! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 4/17/1999 20:30'!processPoints: vertexBuffer "Process a series of points defined by the vertex buffer" self error:'Points are not yet implemented'! !!B3DPrimitiveRasterizer methodsFor: 'processing' stamp: 'ar 4/17/1999 21:02'!processPolygon: vb "Process a polygon defined by the vertex buffer" | objSize | objSize _ self primObjectSize + (vb vertexCount * PrimVertexSize) + (vb vertexCount - 2 * 3). self addPrimitiveObject: vb ofSize: objSize.! !!B3DPrimitiveRasterizer methodsFor: 'primitives' stamp: 'ar 4/14/1999 05:12'!primAddObject: obj primitive: primitive vertexArray: vertexArray size: vertexCount indexArray: indexArray size: indexCount viewport: vp textureIndex: txIndex <primitive:'b3dInitPrimitiveObject' module:'Squeak3D'> ^self primitiveFailed! !!B3DPrimitiveRasterizer methodsFor: 'primitives' stamp: 'ar 4/12/1999 02:17'!primObjectSize <primitive: 'b3dPrimitiveObjectSize' module:'Squeak3D'> ^self primitiveFailed! !!B3DPrimitiveRasterizer methodsFor: 'primitives' stamp: 'ar 4/14/1999 05:18'!primStartRasterizer: primState objects: primitiveObjects textures: textureArray "Primitive. Start the rasterizer. Return an error code." <primitive:'b3dStartRasterizer' module:'Squeak3D'> ^self primitiveFailed! !!B3DPrimitiveRasterizer methodsFor: 'private' stamp: 'ar 4/13/1999 02:13'!printSpaceUsage: objects "Print out the maximum space used for processing the given objects" | spaceUsed | spaceUsed _ state spaceUsed. objects do:[:obj| spaceUsed _ spaceUsed + obj basicSize]. spaceUsed _ spaceUsed * 4. Transcript cr; nextPutAll: spaceUsed asStringWithCommas; nextPutAll:' bytes max working set'; endEntry.! !!B3DPrimitiveRasterizer class methodsFor: 'class initialization' stamp: 'ar 4/13/1999 01:52'!initialize "B3DPrimitiveRasterizer initialize" B3DNoMoreEdges _ 1. B3DNoMoreFaces _ 2. B3DNoMoreAttrs _ 3. B3DNoMoreAET _ 4. B3DNoMoreAdded _ 5.! !!B3DPrimitiveRasterizer class methodsFor: 'accessing' stamp: 'ar 4/12/1999 03:46'!version "B3DPrimitiveRasterizer version" <primitive:'b3dRasterizerVersion' module:'Squeak3D'> ^0! !!B3DPrimitiveRasterizer class methodsFor: 'testing' stamp: 'ar 4/12/1999 03:48'!isAvailable ^self version > 0! !!B3DPrimitiveRasterizer class methodsFor: 'private' stamp: 'ar 5/28/2000 22:17'!primitiveSetBitBltPlugin: pluginName <primitive: 'primitiveSetBitBltPlugin' module: 'Squeak3D'> ^nil! !Instances of this class represent data on the primitive level. The major reason for the existance of this class is that all memory needed by the rasterizer is allocated from Smalltalk code[*]. Instances of this class should not be modified from Smalltalk code - they may contain pointers to other memory locations and thus modification of these instances could easily break the system.[*] This is for two reasons: * Some systems (e.g., Mac) don't have the necessary allocation facilities from the primitive level (This REALLY sucks. We have 1999 and MacOS 8.5.1 still has static memory allocation!!) * Allocation from Smalltalk allows us to share memory between Smalltalk and C code, take advantage of GCs if the physically available space is small (e.g., on PDAs) as well as gracefully failing if there is no memory left (e.g., by signalling the low space condition).!!B3DPrimitiveRasterizerData methodsFor: 'accessing' stamp: 'ar 4/10/1999 05:36'!at: index put: value "See the class comment" ^self error:'You must not modify primitive level data'! !!B3DPrimitiveRasterizerData methodsFor: 'accessing' stamp: 'ar 11/7/1999 18:09'!integerAt: index "Return the integer at the given index" | word | word _ self basicAt: index. word < 16r3FFFFFFF ifTrue:[^word]. "Avoid LargeInteger computations" ^word >= 16r80000000 "Negative?!!" ifTrue:["word - 16r100000000" (word bitInvert32 + 1) negated] ifFalse:[word]! !!B3DPrimitiveRasterizerData methodsFor: 'private' stamp: 'ar 4/12/1999 02:36'!replaceFrom: start to: stop with: replacement startingAt: repStart "Private. Used for growing rasterizer data only." <primitive: 105> ^self primitiveFailed! !This class represents a set of objects that are known to the primitive level rasterizer. It should not be modified unless you know *exactly* what you're doing. The instance variables could actually be indexed but I decided to give them names for readability.Instance variables: faceAlloc <B3DPrimitiveRasterizerData> - Source for primitive level face allocation. edgeAlloc <B3DPrimitiveRasterizerData> - Source for primitive level edge allocation. attrAlloc <B3DPrimitiveRasterizerData> - Source for primitive level attribute allocation. aet <B3DPrimitiveRasterizerData> - Primitive level active edge table. addedEdges <B3DPrimitiveRasterizerData> - Primitive level temporary edge storage. fillList <B3DPrimitiveRasterizerData> - Primitive level fill list. objects <B3DPrimitiveRasterizerData> - Primitive level list of objects. textures <B3DPrimitiveRasterizerData> - Primitive level lists of textures. spanBuffer <Bitmap> - 32bit bitmap to render into bitBlt <BitBlt> - Final output device!!B3DPrimitiveRasterizerState methodsFor: 'initialize' stamp: 'ar 4/14/1999 05:14'!initObjects: nObjects objects _ B3DPrimitiveRasterizerData new: nObjects! !!B3DPrimitiveRasterizerState methodsFor: 'initialize' stamp: 'ar 4/14/1999 05:13'!initTextures: nTextures textures _ B3DPrimitiveRasterizerData new: (self primTextureSize * nTextures).! !!B3DPrimitiveRasterizerState methodsFor: 'initialize' stamp: 'ar 4/13/1999 06:29'!initialize faceAlloc ifNil:[faceAlloc _ B3DPrimitiveRasterizerData new: 32768]. edgeAlloc ifNil:[edgeAlloc _ B3DPrimitiveRasterizerData new: 16384]. attrAlloc ifNil:[attrAlloc _ B3DPrimitiveRasterizerData new: 4096]. aet ifNil:[aet _ B3DPrimitiveRasterizerData new: 4096]. addedEdges ifNil:[addedEdges _ B3DPrimitiveRasterizerData new: 4096]. fillList ifNil:[fillList _ B3DPrimitiveRasterizerData new: 32]. self primInitializeBuffers.! !!B3DPrimitiveRasterizerState methodsFor: 'initialize' stamp: 'ar 4/11/1999 23:47'!reset self primInitializeBuffers.! !!B3DPrimitiveRasterizerState methodsFor: 'accessing' stamp: 'ar 4/13/1999 00:10'!bitBlt ^bitBlt! !!B3DPrimitiveRasterizerState methodsFor: 'accessing' stamp: 'ar 4/13/1999 00:10'!bitBlt: aBitBlt bitBlt _ aBitBlt.! !!B3DPrimitiveRasterizerState methodsFor: 'accessing' stamp: 'ar 4/13/1999 02:09'!spaceUsed ^faceAlloc basicSize + edgeAlloc basicSize + attrAlloc basicSize + aet basicSize + addedEdges basicSize + fillList basicSize + objects basicSize + spanBuffer basicSize! !!B3DPrimitiveRasterizerState methodsFor: 'accessing' stamp: 'ar 4/13/1999 00:10'!spanBuffer ^spanBuffer! !!B3DPrimitiveRasterizerState methodsFor: 'accessing' stamp: 'ar 4/13/1999 00:10'!spanBuffer: aBitmap spanBuffer _ aBitmap.! !!B3DPrimitiveRasterizerState methodsFor: 'growing' stamp: 'ar 4/14/1999 01:45'!grow: anArray | newArray | newArray _ anArray species new: anArray size + (anArray size // 4 max: 100). newArray replaceFrom: 1 to: anArray size with: anArray startingAt: 1. ^newArray! !!B3DPrimitiveRasterizerState methodsFor: 'growing' stamp: 'ar 4/13/1999 06:30'!growAET "Transcript cr; show:'Growing AET'." aet _ self grow: aet.! !!B3DPrimitiveRasterizerState methodsFor: 'growing' stamp: 'ar 4/13/1999 06:30'!growAdded "Transcript cr; show:'Growing addedEdges'." aet _ self grow: addedEdges.! !!B3DPrimitiveRasterizerState methodsFor: 'growing' stamp: 'ar 4/13/1999 06:30'!growAttrs "Transcript cr; show:'Growing attrAlloc'." attrAlloc _ self grow: attrAlloc.! !!B3DPrimitiveRasterizerState methodsFor: 'growing' stamp: 'ar 4/13/1999 06:30'!growEdges "Transcript cr; show:'Growing edgeAlloc'." edgeAlloc _ self grow: edgeAlloc.! !!B3DPrimitiveRasterizerState methodsFor: 'growing' stamp: 'ar 4/13/1999 06:30'!growFaces "Transcript cr; show:'Growing faceAlloc'." faceAlloc _ self grow: faceAlloc.! !!B3DPrimitiveRasterizerState methodsFor: 'private' stamp: 'ar 4/10/1999 21:29'!primInitializeBuffers <primitive: 'b3dInitializeRasterizerState' module:'Squeak3D'> ^self primitiveFailed! !!B3DPrimitiveRasterizerState methodsFor: 'private' stamp: 'ar 4/14/1999 05:13'!primTextureSize <primitive:'b3dPrimitiveTextureSize' module:'Squeak3D'> ^self primitiveFailed! !I am a shader that uses primitive level support.NOTE: Currently, primitive and non-primitive lights cannot be mixed.!!B3DPrimitiveShader methodsFor: 'initialize' stamp: 'ar 2/17/1999 04:17'!initialize super initialize. primitiveLights _ #().! !!B3DPrimitiveShader methodsFor: 'initialize' stamp: 'ar 4/10/1999 22:56'!reset super reset. primitiveLights _ #().! !!B3DPrimitiveShader methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:14'!addLight: aLightSource "NOTE: This does not work if primitive/non-primitive lights are mixed!!" | primLight | self flag: #b3dBug. "See above" primLight _ aLightSource asPrimitiveLight. primLight ifNotNil:[primitiveLights _ primitiveLights copyWith: primLight]. ^super addLight: aLightSource! !!B3DPrimitiveShader methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:17'!removeLight: lightIndex | pLight | super removeLight: lightIndex. self flag: #b3dBug. "There should be a better way then doing this." primitiveLights _ #(). lights do:[:light| light ifNotNil:[pLight _ light asPrimitiveLight]. pLight ifNotNil:[primitiveLights _ primitiveLights copyWith: pLight]].! !!B3DPrimitiveShader methodsFor: 'shading' stamp: 'ar 2/17/1999 04:10'!primShadeVB: vertexArray count: vtxCount lights: lightArray material: aMaterial vbFlags: vbFlags "Primitive. Shade all the vertices in the vertex buffer using the given array of primitive light sources. Return true on success, false otherwise." <primitive: 'b3dShadeVertexBuffer' module:'Squeak3D'> self flag: #b3dDebug. self primitiveFailed. ^false! !!B3DPrimitiveShader methodsFor: 'shading' stamp: 'ar 2/17/1999 04:11'!processVertexBuffer: vb "Do the primitive operation" (self primShadeVB: vb vertexArray count: vb vertexCount lights: primitiveLights material: material vbFlags: vb flags) ifTrue:[^self]. "Run simulation instead" super processVertexBuffer: vb.! !!B3DPrimitiveShader class methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:09'!version "Return the version of this shader" <primitive:'b3dShaderVersion' module:'Squeak3D'> ^0! !!B3DPrimitiveShader class methodsFor: 'testing' stamp: 'ar 2/17/1999 04:08'!isAvailable ^self version > 0! !I am a vertex transformer that uses some primitive level support.!!B3DPrimitiveTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:19'!privateTransformMatrix: m1 with: m2 into: m3 "Use the primitive operation" <primitive: 'b3dTransformMatrixWithInto' module:'Squeak3D'> ^super privateTransformMatrix: m1 with: m2 into: m3! !!B3DPrimitiveTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:20'!privateTransformPrimitiveNormal: primitiveVertex byMatrix: aMatrix rescale: scaleNeeded "Use the primitive operation" <primitive: 'b3dTransformPrimitiveNormal' module:'Squeak3D'> ^super privateTransformPrimitiveNormal: primitiveVertex byMatrix: aMatrix rescale: scaleNeeded! !!B3DPrimitiveTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:20'!privateTransformPrimitiveVertex: primitiveVertex byModelView: aMatrix "Use the primitive operation" <primitive: 'b3dTransformPrimitivePosition' module:'Squeak3D'> ^super privateTransformPrimitiveVertex: primitiveVertex byModelView: aMatrix! !!B3DPrimitiveTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:21'!privateTransformPrimitiveVertex: primitiveVertex byProjection: aMatrix "Use the primitive operation" <primitive: 'b3dTransformPrimitiveRasterPosition' module:'Squeak3D'> ^super privateTransformPrimitiveVertex: primitiveVertex byProjection: aMatrix! !!B3DPrimitiveTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:21'!privateTransformVB: vertexArray count: vertexCount modelViewMatrix: modelViewMatrix projectionMatrix: projectionMatrix flags: flags "Use the primitive operation" <primitive: 'b3dTransformVertexBuffer' module:'Squeak3D'> ^super privateTransformVB: vertexArray count: vertexCount modelViewMatrix: modelViewMatrix projectionMatrix: projectionMatrix flags: flags! !!B3DPrimitiveTransformer class methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:29'!version "Return the version of this transformer" <primitive:'b3dTransformerVersion' module:'Squeak3D'> ^0! !!B3DPrimitiveTransformer class methodsFor: 'testing' stamp: 'ar 2/17/1999 04:22'!isAvailable ^self version > 0! !I represent all per vertex information used in Balloon 3D primitive operations. I store either 32bit floats or integers depending on what is requested.C representation: typedef struct B3DPrimitiveVertex { float position[3]; float normal[3]; float texCoord[2]; float rasterPos[4]; int pixelValue32; int clipFlags; int windowPos[2]; } B3DPrimitiveVertex;!!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/5/1999 19:27'!b3dColor ^self color asB3DColor! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/5/1999 19:28'!b3dColor: aB3DColor4 self color: aB3DColor4 asColor! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/4/1999 23:53'!clipFlags ^self wordAt: 14! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/4/1999 23:53'!clipFlags: aNumber self wordAt: 14 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'accessing'!color ^self pixelValue32 asColorOfDepth: 32! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/4/1999 20:21'!color: aColor self pixelValue32: (aColor asColor pixelWordForDepth: 32)! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/5/1999 19:20'!floatAt: index <primitive:'primitiveFloatArrayAt'> ^Float fromIEEE32Bit: (self basicAt: index)! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/5/1999 19:21'!floatAt: index put: value <primitive:'primitiveFloatArrayAtPut'> value isFloat ifTrue:[self basicAt: index put: value asIEEE32BitWord] ifFalse:[self at: index put: value asFloat]. ^value! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 4/4/1999 00:29'!integerAt: index | word | word _ self basicAt: index. word < 16r3FFFFFFF ifTrue:[^word]. "Avoid LargeInteger computations" ^word >= 16r80000000 "Negative?!!" ifTrue:["word - 16r100000000" (word bitInvert32 + 1) negated] ifFalse:[word]! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 4/4/1999 00:29'!integerAt: index put: anInteger | word | anInteger < 0 ifTrue:["word _ 16r100000000 + anInteger" word _ (anInteger + 1) negated bitInvert32] ifFalse:[word _ anInteger]. self basicAt: index put: word. ^anInteger! !!B3DPrimitiveVertex methodsFor: 'accessing'!normal ^B3DVector3 x: (self floatAt: 4) y: (self floatAt: 5) z: (self floatAt: 6)! !!B3DPrimitiveVertex methodsFor: 'accessing'!normal: aVector self floatAt: 4 put: aVector x. self floatAt: 5 put: aVector y. self floatAt: 6 put: aVector z.! !!B3DPrimitiveVertex methodsFor: 'accessing'!pixelValue32 ^self wordAt: 13! !!B3DPrimitiveVertex methodsFor: 'accessing'!pixelValue32: aNumber self wordAt: 13 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'accessing'!position ^B3DVector3 x: (self floatAt: 1) y: (self floatAt: 2) z: (self floatAt: 3)! !!B3DPrimitiveVertex methodsFor: 'accessing'!position: aVector self floatAt: 1 put: aVector x. self floatAt: 2 put: aVector y. self floatAt: 3 put: aVector z.! !!B3DPrimitiveVertex methodsFor: 'accessing'!rasterPos ^B3DVector4 x: (self floatAt: 9) y: (self floatAt: 10) z: (self floatAt: 11) w: (self floatAt: 12)! !!B3DPrimitiveVertex methodsFor: 'accessing'!rasterPos: aVector self floatAt: 9 put: aVector x. self floatAt: 10 put: aVector y. self floatAt: 11 put: aVector z. self floatAt: 12 put: aVector w.! !!B3DPrimitiveVertex methodsFor: 'accessing'!texCoords ^(self floatAt: 7) @ (self floatAt: 8)! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 2/5/1999 19:30'!texCoords: aVector self floatAt: 7 put: aVector x. self floatAt: 8 put: aVector y.! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 4/4/1999 00:21'!windowPos ^self windowPosX@self windowPosY! !!B3DPrimitiveVertex methodsFor: 'accessing' stamp: 'ar 4/4/1999 00:22'!windowPos: aPoint self windowPosX: aPoint x. self windowPosY: aPoint y.! !!B3DPrimitiveVertex methodsFor: 'accessing'!wordAt: index <primitive: 60> ^self primitiveFailed! !!B3DPrimitiveVertex methodsFor: 'accessing'!wordAt: index put: value <primitive: 61> ^self primitiveFailed! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 2/8/1999 17:48'!normalX ^self floatAt: 4! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 2/8/1999 17:50'!normalX: aFloat self floatAt: 4 put: aFloat! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 2/8/1999 17:48'!normalY ^self floatAt: 5! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 2/8/1999 17:50'!normalY: aFloat self floatAt: 5 put: aFloat! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 2/8/1999 17:48'!normalZ ^self floatAt: 6! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 2/8/1999 17:50'!normalZ: aFloat self floatAt: 6 put: aFloat! !!B3DPrimitiveVertex methodsFor: 'transform-support'!positionX ^self floatAt: 1! !!B3DPrimitiveVertex methodsFor: 'transform-support'!positionX: aNumber self floatAt: 1 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support'!positionY ^self floatAt: 2! !!B3DPrimitiveVertex methodsFor: 'transform-support'!positionY: aNumber self floatAt: 2 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support'!positionZ ^self floatAt: 3! !!B3DPrimitiveVertex methodsFor: 'transform-support'!positionZ: aNumber self floatAt: 3 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosW ^self floatAt: 12! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosW: aNumber self floatAt: 12 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosX ^self floatAt: 9! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosX: aNumber self floatAt: 9 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosY ^self floatAt: 10! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosY: aNumber self floatAt: 10 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosZ ^self floatAt: 11! !!B3DPrimitiveVertex methodsFor: 'transform-support'!rasterPosZ: aNumber self floatAt: 11 put: aNumber! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 4/4/1999 00:31'!windowPosX ^self integerAt: 15! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 4/4/1999 00:31'!windowPosX: anInteger self integerAt: 15 put: anInteger! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 4/4/1999 00:31'!windowPosY ^self integerAt: 16! !!B3DPrimitiveVertex methodsFor: 'transform-support' stamp: 'ar 4/4/1999 00:31'!windowPosY: anInteger self integerAt: 16 put: anInteger! !!B3DPrimitiveVertex methodsFor: 'private'!privateReplaceFrom: start to: stop with: replacement startingAt: repStart <primitive: 105> start to: stop do:[:i| self basicAt: i put: (replacement basicAt: i - start + repStart). ].! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:27'!aValue ^self pixelValue32 bitShift: -24! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:29'!alphaValue ^self pixelValue32 bitShift: -24! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:28'!bValue ^self pixelValue32 bitAnd: 255! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:29'!blueValue ^self pixelValue32 bitAnd: 255! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:28'!gValue ^(self pixelValue32 bitShift: -8) bitAnd: 255! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:29'!greenValue ^(self pixelValue32 bitShift: -8) bitAnd: 255! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:28'!rValue ^(self pixelValue32 bitShift: -16) bitAnd: 255! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/6/1999 22:29'!redValue ^(self pixelValue32 bitShift: -16) bitAnd: 255! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/18/1999 06:26'!texCoordS ^self floatAt: 7! !!B3DPrimitiveVertex methodsFor: 'rasterizer-support' stamp: 'ar 4/18/1999 06:26'!texCoordT ^self floatAt: 8! !!B3DPrimitiveVertex methodsFor: 'testing' stamp: 'ar 4/4/1999 00:50'!sortsBefore: pVertex "Return true if the receiver should be sorted before the given primitive vertex. Support for rasterizer simulation. Only valid if window position has been computed before." | y0 y1 | y0 _ self windowPosY. y1 _ pVertex windowPosY. y0 = y1 ifTrue:[^self windowPosX <= pVertex windowPosX] ifFalse:[^y0 < y1]! !!B3DPrimitiveVertex class methodsFor: 'instance creation' stamp: 'ar 2/14/1999 01:23'!new ^self new: PrimVertexSize! !I store Balloon 3D primitive vertices in place. I am used to pass data efficiently to the primitive level during high-bandwidth operations.!!B3DPrimitiveVertexArray methodsFor: 'accessing' stamp: 'ar 2/14/1999 01:24'!at: index "Return the primitive vertex at the given index" | vtx | (index < 1 or:[index > self size]) ifTrue:[^self errorSubscriptBounds: index]. vtx _ B3DPrimitiveVertex new. vtx privateReplaceFrom: 1 to: vtx size with: self startingAt: index-1*PrimVertexSize+1. ^vtx! !!B3DPrimitiveVertexArray methodsFor: 'accessing' stamp: 'ar 2/14/1999 01:24'!at: index put: aB3DPrimitiveVertex "Store the primitive vertex at the given index in the receiver" | idx | (index < 1 or:[index > self size]) ifTrue:[^self errorSubscriptBounds: index]. idx _ index-1*PrimVertexSize. self privateReplaceFrom: idx+1 to: idx+PrimVertexSize with: aB3DPrimitiveVertex startingAt: 1. ^aB3DPrimitiveVertex! !!B3DPrimitiveVertexArray methodsFor: 'accessing' stamp: 'ar 2/14/1999 01:24'!size "Return the number of primitive vertices that can be stored in the receiver" ^self basicSize // PrimVertexSize! !!B3DPrimitiveVertexArray methodsFor: 'private'!privateReplaceFrom: start to: stop with: replacement startingAt: repStart <primitive: 105> start to: stop do:[:i| self basicAt: i put: (replacement at: i - start + repStart). ].! !!B3DPrimitiveVertexArray methodsFor: 'enumerating' stamp: 'ar 2/4/1999 23:57'!upTo: max do: aBlock "Special enumeration message so the client can modify the vertices" | vtx | 1 to: max do:[:i| vtx _ self at: i. aBlock value: vtx. self at: i put: vtx].! !!B3DPrimitiveVertexArray methodsFor: 'enumerating' stamp: 'ar 2/4/1999 23:59'!upTo: max doWithIndex: aBlock "Special enumeration message so the client can modify the vertices" | vtx | 1 to: max do:[:i| vtx _ self at: i. aBlock value: vtx value: i. self at: i put: vtx].! !!B3DPrimitiveVertexArray class methodsFor: 'instance creation' stamp: 'ar 2/14/1999 01:24'!new: n ^super new: (n * PrimVertexSize)! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 4/17/1999 20:57'!b3dInitPrimitiveObject | vtxSize vtxArray idxSize idxArray primitive primOop primObj primSize textureIndex | self export: true. self inline: false. self var: #vtxArray declareC:'int *vtxArray'. self var: #idxArray declareC:'int *idxArray'. self var: #primObj declareC:'void *primObj'. "Check argument count" interpreterProxy methodArgumentCount = 8 ifFalse:[^interpreterProxy primitiveFail]. "Fetch the texture index" textureIndex _ interpreterProxy stackIntegerValue: 0. interpreterProxy failed ifTrue:[^nil]. "Load the viewport" self loadViewportFrom: 1. interpreterProxy failed ifTrue:[^nil]. "Fetch and validate the primitive vertex array" vtxSize _ interpreterProxy stackIntegerValue: 4. vtxArray _ self stackPrimitiveVertexArray: 5 ofSize: vtxSize. vtxArray = nil ifTrue:[^interpreterProxy primitiveFail]. "Fetch and validate the primitive index array" idxSize _ interpreterProxy stackIntegerValue: 2. idxArray _ self stackPrimitiveIndexArray: 3 ofSize: idxSize validate: true forVertexSize: vtxSize. idxArray = nil ifTrue:[^interpreterProxy primitiveFail]. "Fetch and validate the primitive type" primitive _ interpreterProxy stackIntegerValue: 6. (primitive < 1 or:[primitive > PrimTypeMax]) ifTrue:[^interpreterProxy primitiveFail]. "For now we only support indexed triangles, quads and polys" (primitive = 3 or:[primitive = 5 or:[primitive = 6]]) ifFalse:[^interpreterProxy primitiveFail]. "Load the primitive object" primOop _ interpreterProxy stackObjectValue: 7. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy isWords: primOop) ifFalse:[^interpreterProxy primitiveFail]. primObj _ interpreterProxy firstIndexableField: primOop. primSize _ interpreterProxy byteSizeOf: primOop. "Do the work" primitive = 3 ifTrue:[ (self cCode: 'b3dAddPolygonObject((void*) primObj, primSize, B3D_FACE_RGB, textureIndex, (B3DPrimitiveVertex*) vtxArray, vtxSize, &viewport) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. ]. primitive = 5 ifTrue:[ (self cCode:'b3dAddIndexedTriangleObject((void*) primObj, primSize, B3D_FACE_RGB, textureIndex, (B3DPrimitiveVertex*) vtxArray, vtxSize, (B3DInputFace*) idxArray, idxSize / 3, &viewport) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. ]. primitive = 6 ifTrue:[ (self cCode:'b3dAddIndexedQuadObject((void*) primObj, primSize, B3D_FACE_RGB, textureIndex, (B3DPrimitiveVertex*) vtxArray, vtxSize, (B3DInputQuad*) idxArray, idxSize / 4, &viewport) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. ]. "Pop args+rcvr; return primitive object" interpreterProxy pop: 9. interpreterProxy push: primOop.! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 4/14/1999 05:59'!b3dInitializeRasterizerState "Primitive. Initialize the primitive level objects of the given rasterizer." | stateOop objOop objLen obj | self export: true. self inline: false. self var: #obj declareC:'void *obj'. "Check argument count" interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. stateOop _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. ((interpreterProxy isPointers: stateOop) and:[(interpreterProxy slotSizeOf: stateOop) >= 7]) ifFalse:[^interpreterProxy primitiveFail]. objOop _ interpreterProxy fetchPointer: 0 ofObject: stateOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objLen _ interpreterProxy byteSizeOf: objOop. obj _ interpreterProxy firstIndexableField: objOop. (self cCode: 'b3dInitializeFaceAllocator(obj, objLen) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. objOop _ interpreterProxy fetchPointer: 1 ofObject: stateOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objLen _ interpreterProxy byteSizeOf: objOop. obj _ interpreterProxy firstIndexableField: objOop. (self cCode: 'b3dInitializeEdgeAllocator(obj, objLen) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. objOop _ interpreterProxy fetchPointer: 2 ofObject: stateOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objLen _ interpreterProxy byteSizeOf: objOop. obj _ interpreterProxy firstIndexableField: objOop. (self cCode: 'b3dInitializeAttrAllocator(obj, objLen) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. objOop _ interpreterProxy fetchPointer: 3 ofObject: stateOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objLen _ interpreterProxy byteSizeOf: objOop. obj _ interpreterProxy firstIndexableField: objOop. (self cCode: 'b3dInitializeAET(obj, objLen) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. objOop _ interpreterProxy fetchPointer: 4 ofObject: stateOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objLen _ interpreterProxy byteSizeOf: objOop. obj _ interpreterProxy firstIndexableField: objOop. (self cCode: 'b3dInitializeEdgeList(obj, objLen) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. objOop _ interpreterProxy fetchPointer: 5 ofObject: stateOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objLen _ interpreterProxy byteSizeOf: objOop. obj _ interpreterProxy firstIndexableField: objOop. (self cCode: 'b3dInitializeFillList(obj, objLen) !!= B3D_NO_ERROR') ifTrue:[^interpreterProxy primitiveFail]. "Don't pop anything - return the receiver"! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 4/14/1999 02:06'!b3dPrimitiveObjectSize "Primitive. Return the minimal number of words needed for a primitive object." | objSize | self export: true. self inline: false. objSize _ (self cCode:'sizeof(B3DPrimitiveObject) + sizeof(B3DPrimitiveVertex)') // 4 + 1. interpreterProxy pop: 1. interpreterProxy pushInteger: objSize.! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 4/14/1999 05:22'!b3dPrimitiveTextureSize "Primitive. Return the minimal number of words needed for a primitive object." | objSize | self export: true. self inline: false. objSize _ (self cCode:'sizeof(B3DTexture)') // 4 + 1. interpreterProxy pop: 1. interpreterProxy pushInteger: objSize.! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 4/12/1999 02:19'!b3dRasterizerVersion "Primitive. Return the version of the rasterizer." self export: true. self inline: false. interpreterProxy pop: 1. interpreterProxy pushInteger: 1. "Version 1"! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 4/14/1999 20:45'!b3dStartRasterizer "Primitive. Start the rasterizer." | errCode | self export: true. self inline: false. "Check argument count" interpreterProxy methodArgumentCount = 3 ifFalse:[^interpreterProxy primitiveFail]. "Load the base rasterizer state" (self loadRasterizerState: 2) ifFalse:[^interpreterProxy primitiveFail]. "Load the textures" self loadTexturesFrom: 0. interpreterProxy failed ifTrue:[^nil]. "And the objects" self loadObjectsFrom: 1. interpreterProxy failed ifTrue:[^nil]. "And go ..." errCode _ self cCode:'b3dMainLoop(&state, B3D_NO_ERROR)'. self storeObjectsInto: 1. interpreterProxy pop: 4. interpreterProxy pushInteger: errCode.! !!B3DRasterizerPlugin methodsFor: 'primitives' stamp: 'ar 5/16/2000 20:06'!primitiveSetBitBltPlugin "Primitive. Set the BitBlt plugin to use." | pluginName length ptr needReload | self export: true. self var: #ptr declareC:'char *ptr'. pluginName _ interpreterProxy stackValue: 0. "Must be string to work" (interpreterProxy isBytes: pluginName) ifFalse:[^interpreterProxy primitiveFail]. length _ interpreterProxy byteSizeOf: pluginName. length >= 256 ifTrue:[^interpreterProxy primitiveFail]. ptr _ interpreterProxy firstIndexableField: pluginName. needReload _ false. 0 to: length-1 do:[:i| "Compare and store the plugin to be used" (bbPluginName at: i) = (ptr at: i) ifFalse:[ bbPluginName at: i put: (ptr at: i). needReload _ true]]. (bbPluginName at: length) = 0 ifFalse:[ bbPluginName at: length put: 0. needReload _ true]. needReload ifTrue:[ self initialiseModule ifFalse:[^interpreterProxy primitiveFail]]. interpreterProxy pop: 1. "Return receiver"! !!B3DRasterizerPlugin methodsFor: 'primitive support' stamp: 'ar 4/12/1999 06:02'!loadObjectsFrom: stackIndex | arrayOop arraySize objArray objOop objPtr | self var:#objArray declareC:'B3DPrimitiveObject **objArray'. self var:#objPtr declareC:'B3DPrimitiveObject *objPtr'. arrayOop _ interpreterProxy stackObjectValue: stackIndex. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy fetchClassOf: arrayOop) == (interpreterProxy classArray) ifFalse:[^interpreterProxy primitiveFail]. arraySize _ interpreterProxy slotSizeOf: arrayOop. arraySize > (self cCode:'state.nObjects') ifTrue:[^interpreterProxy primitiveFail]. objArray _ self cCode:'state.objects'. 0 to: arraySize-1 do:[:i| objOop _ interpreterProxy fetchPointer: i ofObject: arrayOop. ((interpreterProxy isIntegerObject: objOop) or:[(interpreterProxy isWords: objOop) not]) ifTrue:[^interpreterProxy primitiveFail]. objPtr _ self cCoerce: (interpreterProxy firstIndexableField: objOop) to:'B3DPrimitiveObject*'. (self cCode:'objPtr->magic !!= B3D_PRIMITIVE_OBJECT_MAGIC') ifTrue:[^interpreterProxy primitiveFail]. self cCode:'objPtr->__oop__ = objOop'. objArray at: i put: objPtr. ].! !!B3DRasterizerPlugin methodsFor: 'primitive support' stamp: 'ar 5/16/2000 17:10'!loadRasterizerState: stackIndex "Load the rasterizer state from the given stack index." | stateOop obj objPtr objLen | self var: #objPtr declareC:'void *objPtr'. (copyBitsFn = 0 or:[loadBBFn = 0]) ifTrue:[ "We need loadBitBltFrom/copyBits here so try to load it implicitly" self initialiseModule ifFalse:[^false]. ]. stateOop _ interpreterProxy stackObjectValue: stackIndex. interpreterProxy failed ifTrue:[^false]. ((interpreterProxy isPointers: stateOop) and:[(interpreterProxy slotSizeOf: stateOop) >= 10]) ifFalse:[^false]. obj _ interpreterProxy fetchPointer: 0 ofObject: stateOop. ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.faceAlloc = objPtr'. obj _ interpreterProxy fetchPointer: 1 ofObject: stateOop. ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.edgeAlloc = objPtr'. obj _ interpreterProxy fetchPointer: 2 ofObject: stateOop. ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.attrAlloc = objPtr'. obj _ interpreterProxy fetchPointer: 3 ofObject: stateOop. ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.aet = objPtr'. obj _ interpreterProxy fetchPointer: 4 ofObject: stateOop. ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.addedEdges = objPtr'. obj _ interpreterProxy fetchPointer: 5 ofObject: stateOop. ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.fillList = objPtr'. obj _ interpreterProxy fetchPointer: 6 ofObject: stateOop. obj == interpreterProxy nilObject ifTrue:[ self cCode:'state.nObjects = 0'. self cCode:'state.objects = NULL'. ] ifFalse:[ ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objLen _ interpreterProxy slotSizeOf: obj. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.objects = (B3DPrimitiveObject **)objPtr'. self cCode:'state.nObjects = objLen'. ]. obj _ interpreterProxy fetchPointer: 7 ofObject: stateOop. obj == interpreterProxy nilObject ifTrue:[ self cCode:'state.nTextures = 0'. self cCode:'state.textures = NULL'. ] ifFalse:[ ((interpreterProxy isIntegerObject: obj) or:[(interpreterProxy isWords: obj) not]) ifTrue:[^false]. objLen _ interpreterProxy byteSizeOf: obj. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.textures = (B3DTexture *)objPtr'. self cCode:'state.nTextures = objLen / sizeof(B3DTexture)'. ]. obj _ interpreterProxy fetchPointer: 8 ofObject: stateOop. obj == interpreterProxy nilObject ifTrue:[ self cCode:'state.spanSize = 0'. self cCode:'state.spanBuffer = NULL'. ] ifFalse:[ (interpreterProxy fetchClassOf: obj) == (interpreterProxy classBitmap) ifFalse:[^false]. objLen _ interpreterProxy slotSizeOf: obj. objPtr _ interpreterProxy firstIndexableField: obj. self cCode:'state.spanBuffer = (unsigned int *)objPtr'. self cCode:'state.spanSize = objLen'. ]. obj _ interpreterProxy fetchPointer: 9 ofObject: stateOop. obj == interpreterProxy nilObject ifTrue:[ self cCode:'state.spanDrawer = NULL'. ] ifFalse:[ (self cCode: '((int (*) (int))loadBBFn)(obj)') ifFalse:[^false]. self cCode:'state.spanDrawer = (b3dDrawBufferFunction) copyBitsFn'. ]. ^interpreterProxy failed not! !!B3DRasterizerPlugin methodsFor: 'primitive support' stamp: 'ar 4/14/1999 05:50'!loadTexture: textureOop into: destPtr "Note: This still uses the old-style textures" | form formBits formWidth formHeight formDepth texWrap texInterpolate texEnvMode bitsPtr | self var: #bitsPtr declareC:'void *bitsPtr'. self var: #destPtr declareC:'B3DTexture *destPtr'. "Fetch and validate the form" form _ textureOop. (interpreterProxy isPointers: form) ifFalse:[^false]. (interpreterProxy slotSizeOf: form) < 8 ifTrue:[^false]. formBits _ interpreterProxy fetchPointer: 0 ofObject: form. formWidth _ interpreterProxy fetchInteger: 1 ofObject: form. formHeight _ interpreterProxy fetchInteger: 2 ofObject: form. formDepth _ interpreterProxy fetchInteger: 3 ofObject: form. texWrap _ interpreterProxy booleanValueOf: (interpreterProxy fetchPointer: 5 ofObject: form). texInterpolate _ interpreterProxy booleanValueOf: (interpreterProxy fetchPointer: 6 ofObject: form). texEnvMode _ interpreterProxy fetchInteger: 7 ofObject: form. interpreterProxy failed ifTrue:[^false]. (formWidth < 1 or:[formHeight < 1 or:[formDepth ~= 32]]) ifTrue:[^false]. (interpreterProxy fetchClassOf: formBits) = interpreterProxy classBitmap ifFalse:[^false]. (interpreterProxy byteSizeOf: formBits) = (formWidth * formHeight * 4) ifFalse:[^false]. (texEnvMode < 0 or:[texEnvMode > 1]) ifTrue:[^false]. "Now fetch the bits" bitsPtr _ interpreterProxy firstIndexableField: formBits. "Set the texture parameters" ^self cCode:'b3dLoadTexture(destPtr, formWidth, formHeight, formDepth, (unsigned int*) bitsPtr, 0, NULL) == B3D_NO_ERROR'.! !!B3DRasterizerPlugin methodsFor: 'primitive support' stamp: 'ar 4/14/1999 05:52'!loadTexturesFrom: stackIndex | arrayOop destPtr n textureOop | self var: #destPtr declareC:'B3DTexture *destPtr'. arrayOop _ interpreterProxy stackObjectValue: stackIndex. (interpreterProxy fetchClassOf: arrayOop) == interpreterProxy classArray ifFalse:[^interpreterProxy primitiveFail]. n _ interpreterProxy slotSizeOf: arrayOop. n _ n min: (self cCode: 'state.nTextures'). 0 to: n-1 do:[:i| destPtr _ self cCode:'state.textures + i'. textureOop _ interpreterProxy fetchPointer: i ofObject: arrayOop. (self loadTexture: textureOop into: destPtr) ifFalse:[^interpreterProxy primitiveFail]. ]. ^0! !!B3DRasterizerPlugin methodsFor: 'primitive support' stamp: 'ar 4/10/1999 23:24'!loadViewportFrom: stackIndex "Load the viewport from the given stack index" | oop p1 p2 x0 y0 x1 y1 | oop _ interpreterProxy stackObjectValue: stackIndex. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy isPointers: oop) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: oop) < 2 ifTrue:[^interpreterProxy primitiveFail]. p1 _ interpreterProxy fetchPointer: 0 ofObject: oop. p2 _ interpreterProxy fetchPointer: 1 ofObject: oop. (interpreterProxy fetchClassOf: p1) = interpreterProxy classPoint ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy fetchClassOf: p2) = interpreterProxy classPoint ifFalse:[^interpreterProxy primitiveFail]. x0 _ interpreterProxy fetchInteger: 0 ofObject: p1. y0 _ interpreterProxy fetchInteger: 1 ofObject: p1. x1 _ (interpreterProxy fetchInteger: 0 ofObject: p2). y1 _ (interpreterProxy fetchInteger: 1 ofObject: p2). interpreterProxy failed ifTrue:[^nil]. self cCode:'viewport.x0 = x0'. self cCode:'viewport.y0 = y0'. self cCode:'viewport.x1 = x1'. self cCode:'viewport.y1 = y1'. ^0! !!B3DRasterizerPlugin methodsFor: 'primitive support' stamp: 'ar 4/12/1999 06:01'!storeObjectsInto: stackIndex | arrayOop arraySize objOop | arrayOop _ interpreterProxy stackObjectValue: stackIndex. arraySize _ self cCode: 'state.nObjects'. 0 to: arraySize-1 do:[:i| objOop _ self cCode:'state.objects[i]->__oop__'. interpreterProxy storePointer: i ofObject: arrayOop withValue: objOop. ].! !!B3DRasterizerPlugin class methodsFor: 'translation' stamp: 'ar 5/15/2000 23:12'!declareCVarsIn: cg cg addHeaderFile:'"b3d.h"'. cg var: #viewport type: #'B3DPrimitiveViewport'. cg var: #state type: #'B3DRasterizerState'! !!B3DRasterizerPlugin class methodsFor: 'translation' stamp: 'ar 4/18/1999 08:36'!translateSupportCode: cSrc inlining: inlineFlag "Inline the given C support code if inlineFlag is set. Inlining converts any functions of the form: /* INLINE someFunction(args) */ void someFunction(declaration args) { ... actual code ... } /* --INLINE-- */ into #define someFunction(args) \ /* void someFunction(declaration args) */ \ { \ ... actual code ... \ } \ /* --INLINE-- */ thus using a hard way of forcing inlining by the C compiler." | in out postfix line | true ifTrue:[^cSrc]. "Disabled until I had time to actually test it ;-)" inlineFlag ifFalse:[^cSrc]. in _ ReadStream on: cSrc. out _ WriteStream on: (String new: cSrc size). postfix _ ''. [in atEnd] whileFalse:[ line _ in upTo: Character cr. (line includesSubString:' INLINE ') ifTrue:[ "New inline start" postfix _ ' \'. line _ line copyFrom: (line findString: 'INLINE')+6 to: line size. line _ line copyFrom: 1 to: (line findString: '*/')-1. out nextPutAll:'#define'; nextPutAll: line; nextPutAll: postfix; cr. "Next line has function declaration -- comment this out" [line _ in upTo: Character cr. line includes: ${] whileFalse:[ out nextPutAll:'/* '; nextPutAll: line; nextPutAll:' */'; nextPutAll: postfix; cr. ]. (line first = ${) ifTrue:[ out nextPutAll: line; nextPutAll: postfix; cr. ] ifFalse:[ out nextPutAll: '/* '; nextPutAll:(line copyFrom: 1 to: (line findString:'{')-1); nextPutAll:' */'; nextPutAll:(line copyFrom: (line findString:'{') to: line size); nextPutAll: postfix; cr. ]. ] ifFalse:[ (line includesSubString:'--INLINE--') ifTrue:[postfix _ '']. out nextPutAll: line; nextPutAll: postfix; cr. ]. ]. ^out contents. "| fs | fs _ FileStream newFileNamed:'b3dr.c'. fs nextPutAll: (B3DRasterizerPlugin translateSupportCode: B3DRasterizerPlugin b3dRemapC inlining: true). fs close."! !!B3DRasterizerPlugin class methodsFor: 'translation' stamp: 'ar 5/15/2000 23:10'!writeSupportCode: inlineFlag "B3DRasterizerPlugin writeSupportCode: true" "B3DRasterizerPlugin writeSupportCode: false" "Translate all the C support files for the Balloon 3D rasterizer plugin." | src fs | #( (b3dTypesH 'b3dTypes.h') (b3dAllocH 'b3dAlloc.h') (b3dHeaderH 'b3d.h') (b3dInitC 'b3dInit.c') (b3dAllocC 'b3dAlloc.c') (b3dRemapC 'b3dRemap.c') (b3dDrawC 'b3dDraw.c') (b3dMainC 'b3dMain.c') ) do:[:spec| src _ self perform: (spec at: 1). src _ self translateSupportCode: src inlining: inlineFlag. fs _ CrLfFileStream newFileNamed: (spec at: 2). fs nextPutAll: src. fs close. ].! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/18/1999 08:30'!b3dAllocC^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dAlloc.c* CONTENT: Memory allocation for the Balloon 3D rasterizer** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#include <assert.h>#include "b3d.h"#ifdef DEBUG_ALLOC/* DEBUG versions of allocators */B3DPrimitiveFace *dbg_b3dAllocFace(B3DFaceAllocList *list){ B3DPrimitiveFace *result; if(list->firstFree) { result = list->firstFree; list->firstFree = list->firstFree->nextFree; if(result->flags & B3D_ALLOC_FLAG) b3dAbort("list->firstFree has allocation bit set"); } else { if(list->size < list->max) { result = list->data + list->size; list->size++; } else return NULL; } result->nextFree = NULL; result->flags = B3D_ALLOC_FLAG; list->nFree--; return result;}B3DPrimitiveEdge *dbg_b3dAllocEdge(B3DEdgeAllocList *list){ B3DPrimitiveEdge *result; if(list->firstFree) { result = list->firstFree; list->firstFree = list->firstFree->nextFree; if(result->flags & B3D_ALLOC_FLAG) b3dAbort("list->firstFree has allocation bit set"); } else { if(list->size < list->max) { result = list->data + list->size; list->size++; } else return NULL; } result->nextFree = NULL; result->flags = B3D_ALLOC_FLAG; list->nFree--; return result;}void dbg_b3dFreeFace(B3DFaceAllocList *list, B3DPrimitiveFace *face){ if(face < list->data || face >= (list->data + list->size)) b3dAbort("face to free is not in list"); if( !! (face->flags & B3D_ALLOC_FLAG) ) b3dAbort("face to free has no allocation flag set"); face->flags = 0; face->nextFree = list->firstFree; list->firstFree = face; list->nFree++;}void dbg_b3dFreeEdge(B3DEdgeAllocList *list, B3DPrimitiveEdge *edge){ if(edge < list->data || edge >= (list->data + list->size)) b3dAbort("edge to free is not in list"); if( !! (edge->flags & B3D_ALLOC_FLAG) ) b3dAbort("edge to free has no allocation flag set"); edge->flags = 0; edge->nextFree = list->firstFree; list->firstFree = edge; list->nFree++;}B3DPrimitiveAttribute *dbg_b3dAllocSingleAttr(B3DAttrAllocList *list){ B3DPrimitiveAttribute *result; if(list->firstFree) { result = list->firstFree; list->firstFree = list->firstFree->next; } else { if(list->size < list->max) { result = list->data + list->size; list->size++; } else return NULL; } list->nFree--; return result;}int dbg_b3dAllocAttrib(B3DAttrAllocList *attrList, B3DPrimitiveFace *face){ B3DPrimitiveAttribute *firstAttr, *nextAttr; int i, nAttrs = 0; assert(face->attributes == NULL); if(face->flags & B3D_FACE_RGB) nAttrs += 3; if(face->flags & B3D_FACE_ALPHA) nAttrs += 1; if(face->flags & B3D_FACE_STW) nAttrs += 3; if(!!nAttrs) return 1; firstAttr = nextAttr = NULL; for(i=0;i<nAttrs; i++) { nextAttr = dbg_b3dAllocSingleAttr(attrList); if(!!nextAttr) return 0; nextAttr->next = firstAttr; firstAttr = nextAttr; } face->attributes = firstAttr; return 1;}void dbg_b3dFreeAttrib(B3DAttrAllocList *list, B3DPrimitiveFace *face){ B3DPrimitiveAttribute *attr, *nextAttr = face->attributes; while(nextAttr) { attr = nextAttr; nextAttr = attr->next; if(attr < list->data || attr >= (list->data + list->size)) b3dAbort("attributes to free are not in list"); attr->next = list->firstFree; list->firstFree = attr; list->nFree++; }}#endif /* DEBUG */'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/18/1999 08:35'!b3dAllocH^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dAlloc.h* CONTENT: Memory allocation for the Balloon 3D rasterizer** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#ifndef B3D_ALLOC_H#define B3D_ALLOC_H#include "b3dTypes.h"/************************ Allocator definitions ************************/#define B3D_EDGE_ALLOC_MAGIC 0x45443341typedef struct B3DEdgeAllocList { int magic; void *This; int max; /* Note: size is ALWAYS less than max */ int size; int nFree; B3DPrimitiveEdge *firstFree; /* pointer to the first free edge (< max) */ B3DPrimitiveEdge data[1];} B3DEdgeAllocList;#define B3D_FACE_ALLOC_MAGIC 0x46443341typedef struct B3DFaceAllocList { int magic; void *This; int max; /* Note: size is ALWAYS less than max */ int size; int nFree; B3DPrimitiveFace *firstFree; /* pointer to the first free face (< max) */ B3DPrimitiveFace data[1];} B3DFaceAllocList;#define B3D_ATTR_ALLOC_MAGIC 0x41443341typedef struct B3DAttrAllocList { int magic; void *This; int max; /* Note: size is ALWAYS less than max */ int size; int nFree; B3DPrimitiveAttribute *firstFree; /* pointer to the first free attribute (< max) */ B3DPrimitiveAttribute data[1];} B3DAttrAllocList;/* The mapping from face flags to the number of attributes needed */extern int B3D_ATTRIBUTE_SIZES[B3D_MAX_ATTRIBUTES];#define B3D_FACE_ATTRIB_SIZE(face) (B3D_ATTRIBUTE_SIZES[(face->flags >> B3D_ATTR_SHIFT) & B3D_ATTR_MASK])#ifdef DEBUG_ALLOCB3DPrimitiveFace *dbg_b3dAllocFace(B3DFaceAllocList *list);B3DPrimitiveEdge *dbg_b3dAllocEdge(B3DEdgeAllocList *list);int dbg_b3dAllocAttrib(B3DAttrAllocList *attrList, B3DPrimitiveFace *face);void dbg_b3dFreeFace(B3DFaceAllocList *list, B3DPrimitiveFace *face);void dbg_b3dFreeEdge(B3DEdgeAllocList *list, B3DPrimitiveEdge *edge);void dbg_b3dFreeAttrib(B3DAttrAllocList *list, B3DPrimitiveFace *face);#define b3dAllocFace(list, face) face = dbg_b3dAllocFace(list);#define b3dAllocEdge(list, edge) edge = dbg_b3dAllocEdge(list);#define b3dAllocAttrib(attrList, face, result) result = dbg_b3dAllocAttrib(attrList, face);#define b3dFreeFace(list, face) dbg_b3dFreeFace(list, face);#define b3dFreeEdge(list, edge) dbg_b3dFreeEdge(list, edge);#define b3dFreeAttrib(list, face) dbg_b3dFreeAttrib(list, face);#else /* RELEASE */#define b3dAlloc(list,object) \{\ if(list->firstFree) { \ object = list->firstFree; \ list->firstFree = object->nextFree; \ object->flags = B3D_ALLOC_FLAG; \ list->nFree--;\ } else { \ if(list->size < list->max) { \ object = list->data + list->size; \ list->size++;\ object->flags = B3D_ALLOC_FLAG;\ list->nFree--;\ } else object = NULL;\ }\}#define b3dFree(list, object) \{\ object->flags = 0;\ object->nextFree = list->firstFree; \ list->firstFree = object;\ list->nFree++;\}#define b3dAllocFace(list, face) b3dAlloc(list,face)#define b3dAllocEdge(list, edge) b3dAlloc(list, edge)#define b3dFreeFace(list, face) b3dFree(list, face)#define b3dFreeEdge(list, edge) b3dFree(list, edge)#define b3dAllocSingleAttr(list,object) \{\ if(list->firstFree) { \ object = list->firstFree; \ list->firstFree = object->next; \ list->nFree--;\ } else { \ if(list->size < list->max) { \ object = list->data + list->size; \ list->size++;\ list->nFree--;\ } else object = NULL;\ }\}#define b3dAllocAttrib(attrList,face, result) \{\ B3DPrimitiveAttribute *firstAttr, *nextAttr;\ int nAttrs = 0;\\ if(face->flags & B3D_FACE_RGB) nAttrs += 3;\ if(face->flags & B3D_FACE_ALPHA) nAttrs += 1;\ if(face->flags & B3D_FACE_STW) nAttrs += 3;\ firstAttr = nextAttr = NULL;\ while(nAttrs--) {\ b3dAllocSingleAttr(attrList, nextAttr);\ if(!!nextAttr) break;\ nextAttr->next = firstAttr;\ firstAttr = nextAttr;\ };\ face->attributes = firstAttr;\ result = nextAttr !!= NULL;\}#define b3dFreeAttrib(list, face) \{\ B3DPrimitiveAttribute *attr, *nextAttr = face->attributes;\ while(nextAttr) {\ attr = nextAttr;\ nextAttr = attr->next;\ attr->next = list->firstFree;\ list->firstFree = attr;\ list->nFree++;\ }\}#endif#endif /* ifndef B3D_ALLOC_H */'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/21/1999 01:58'!b3dDrawC^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dDraw.c* CONTENT: Pixel drawing functions for the B3D rasterizer** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES: LOTS of stuff missing here...** - A note on RGBA interpolation:* For low polygon models it makes sense to compute both, the left and* the right attribute value if there might be any overflow at all.* Since we''re usually drawing many pixels in a row we can clamp the* left and right value and thus be safe during the interpolation stage.******************************************************************************/#include "b3d.h"#define rasterPosX rasterPos[0]#define rasterPosY rasterPos[1]#define redValue color[RED_INDEX]#define greenValue color[GREEN_INDEX]#define blueValue color[BLUE_INDEX]#define alphaValue color[ALPHA_INDEX]/* The following defines the maximum number of pixels we treat in one loop. This value should be carefully chosen: Setting it high will increase speed for larger polygons but reduce speed for smaller ones. Setting it low will do the opposite. Also, since I''m assuming a smart compiler, the code size will probably increase with this number (if loops are unrolled by the compiler). The current value of 5 should be a good median (32 pixels are processed at most and we''ll have the overhead of 5 tests for a one-pixel polygon).*/#define MAX_PIXEL_SHIFT 5/* USE_MULTBL: Replace up a couple of multiplications by table lookups. On PowerPC, the lookup seems to be slightly slower. On Intel, the lookup is way faster.*/#ifndef USE_MULTBL# ifdef __POWERPC__# define USE_MULTBL 0# else# define USE_MULTBL 1# endif#endif/* Clamp the given value */#define CLAMP(value, min, max)\ if((value) < (min)) (value) = (min); \ else if((value) > (max)) (value) = (max);/* Clamp a set of fixed point RGB values */#define CLAMP_RGB(r,g,b) \ CLAMP(r,B3D_FixedHalf, (255 << B3D_IntToFixedShift) + B3D_FixedHalf)\ CLAMP(g,B3D_FixedHalf, (255 << B3D_IntToFixedShift) + B3D_FixedHalf)\ CLAMP(b,B3D_FixedHalf, (255 << B3D_IntToFixedShift) + B3D_FixedHalf)#ifdef DEBUG_ATTRdouble attrValueAt(B3DPrimitiveFace *face, B3DPrimitiveAttribute *attr, double xValue, double yValue){ return (attr->value + ((xValue - face->v0->rasterPosX) * attr->dvdx) + ((yValue - face->v0->rasterPosY) * attr->dvdy));}#else#define attrValueAt(face,attr,xValue,yValue) \ ((attr)->value + \ (((double)(xValue) - (face)->v0->rasterPosX) * (attr)->dvdx) + \ (((double)(yValue) - (face)->v0->rasterPosY) * (attr)->dvdy))#endif#define SETUP_RGB \ rValue = (int)(attrValueAt(face, attr, floatX, floatY) * B3D_FloatToFixed); \ deltaR = (int) (attr->dvdx * B3D_FloatToFixed); \ attr = attr->next; \ gValue = (int)(attrValueAt(face, attr, floatX, floatY) * B3D_FloatToFixed);\ deltaG = (int) (attr->dvdx * B3D_FloatToFixed); \ attr = attr->next; \ bValue = (int)(attrValueAt(face, attr, floatX, floatY) * B3D_FloatToFixed); \ deltaB = (int) (attr->dvdx * B3D_FloatToFixed); \ attr = attr->next;\ CLAMP_RGB(rValue, gValue, bValue);#define SETUP_STW \ wValue = attrValueAt(face, attr, floatX, floatY); \ wDelta = attr->dvdx; \ attr = attr->next; \ sValue = attrValueAt(face, attr, floatX, floatY); \ sDelta = attr->dvdx; \ attr = attr->next; \ tValue = attrValueAt(face, attr, floatX, floatY); \ tDelta = attr->dvdx; \ attr = attr->next;#define STEP_STW \ sValue += sDelta;\ tValue += tDelta;\ wValue += wDelta;/* Load the four neighbouring texels into tex00, tex01, tex10, and tex11 */#define LOAD_4_RGB_TEXEL_32(fixedS, fixedT, texture) \{\ int sIndex, tIndex;\\ if(texture->sMask) {\ sIndex = (fixedS >> B3D_FixedToIntShift) & texture->sMask;\ } else {\ sIndex = (fixedS >> B3D_FixedToIntShift) % texture->width;\ }\ if(texture->tMask) {\ tIndex = (fixedT >> B3D_FixedToIntShift) & texture->tMask;\ } else {\ tIndex = (fixedT >> B3D_FixedToIntShift) % texture->height;\ }\ /* Load the 4 texels, wrapping if necessary */\ tex00 = (struct b3dPixelColor *) texture->data + (tIndex * texture->width) + sIndex;\ tex01 = tex00 + 1;\ tex10 = tex00 + texture->width;\ tex11 = tex10 + 1;\ if(sIndex+1 == texture->width) {\ tex01 -= texture->width;\ tex11 -= texture->width;\ }\ if(tIndex+1 == texture->height) {\ int tsize = texture->height * texture->width;\ tex10 -= tsize;\ tex11 -= tsize;\ }\}#if USE_MULTBL /* Use a 16x256 table for lookups */unsigned short MULTBL[17][256];static int multblInit = 0;static void MULTBL_Init(void){ int i,j; for(i=0;i<17;i++) for(j=0; j<256; j++) MULTBL[i][j] = (i*j) >> 4; multblInit = 1;}#define INIT_MULTBL { if (!!multblInit) MULTBL_Init(); }#define DO_RGB_INTERPOLATION(sf, si, tf, ti) \ tr = (MULTBL[ti][(MULTBL[si][tex00->redValue] + MULTBL[sf][tex01->redValue])] + \ MULTBL[tf][(MULTBL[si][tex10->redValue] + MULTBL[sf][tex11->redValue])]);\ tg = (MULTBL[ti][(MULTBL[si][tex00->greenValue] + MULTBL[sf][tex01->greenValue])] + \ MULTBL[tf][(MULTBL[si][tex10->greenValue] + MULTBL[sf][tex11->greenValue])]);\ tb = (MULTBL[ti][(MULTBL[si][tex00->blueValue] + MULTBL[sf][tex01->blueValue])] + \ MULTBL[tf][(MULTBL[si][tex10->blueValue] + MULTBL[sf][tex11->blueValue])]);#define DO_RGBA_INTERPOLATION(sf, si, tf, ti)\ tr = (MULTBL[ti][(MULTBL[si][tex00->redValue] + MULTBL[sf][tex01->redValue])] + \ MULTBL[tf][(MULTBL[si][tex10->redValue] + MULTBL[sf][tex11->redValue])]);\ tg = (MULTBL[ti][(MULTBL[si][tex00->greenValue] + MULTBL[sf][tex01->greenValue])] + \ MULTBL[tf][(MULTBL[si][tex10->greenValue] + MULTBL[sf][tex11->greenValue])]);\ tb = (MULTBL[ti][(MULTBL[si][tex00->blueValue] + MULTBL[sf][tex01->blueValue])] + \ MULTBL[tf][(MULTBL[si][tex10->blueValue] + MULTBL[sf][tex11->blueValue])]); \ ta = (MULTBL[ti][(MULTBL[si][tex00->alphaValue] + MULTBL[sf][tex01->alphaValue])] + \ MULTBL[tf][(MULTBL[si][tex10->alphaValue] + MULTBL[sf][tex11->alphaValue])]);#else#define INIT_MULTBL#define DO_RGB_INTERPOLATION(sf, si, tf, ti) \ tr = (ti * (si * tex00->redValue + sf * tex01->redValue) +\ tf * (si * tex10->redValue + sf * tex11->redValue)) >> 8;\ tg = (ti * (si * tex00->greenValue + sf * tex01->greenValue) +\ tf * (si * tex10->greenValue + sf * tex11->greenValue)) >> 8;\ tb = (ti * (si * tex00->blueValue + sf * tex01->blueValue) +\ tf * (si * tex10->blueValue + sf * tex11->blueValue)) >> 8;\#define DO_RGBA_INTERPOLATION(sf, si, tf, ti) \ tr = (ti * (si * tex00->redValue + sf * tex01->redValue) +\ tf * (si * tex10->redValue + sf * tex11->redValue)) >> 8;\ tg = (ti * (si * tex00->greenValue + sf * tex01->greenValue) +\ tf * (si * tex10->greenValue + sf * tex11->greenValue)) >> 8;\ tb = (ti * (si * tex00->blueValue + sf * tex01->blueValue) +\ tf * (si * tex10->blueValue + sf * tex11->blueValue)) >> 8;\ ta = (ti * (si * tex00->alphaValue + sf * tex01->alphaValue) +\ tf * (si * tex10->alphaValue + sf * tex11->alphaValue)) >> 8;#endif /* No MULTBL */#define INTERPOLATE_RGB_TEXEL(fixedS, fixedT)\{ int sf, si, tf, ti;\ sf = (fixedS >> (B3D_FixedToIntShift - 4)) & 15; si = 16 - sf;\ tf = (fixedT >> (B3D_FixedToIntShift - 4)) & 15; ti = 16 - tf;\ DO_RGB_INTERPOLATION(sf, si, tf, ti)\}void b3dNoDraw (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);void b3dDrawRGB (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);void b3dDrawRGBA (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);void b3dDrawSTW (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);void b3dDrawSTWA (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);void b3dDrawSTWRGB (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);void b3dDrawSTWARGB(int leftX, int rightX, int yValue, B3DPrimitiveFace *face);b3dPixelDrawer B3D_FILL_FUNCTIONS[B3D_MAX_ATTRIBUTES] = { b3dNoDraw, /* No attributes */ b3dDrawRGB, /* B3D_FACE_RGB */ b3dNoDraw, /* B3D_FACE_ALPHA -- IGNORED!!!!!! */ b3dDrawRGBA, /* B3D_FACE_RGB | B3D_FACE_ALPHA */ b3dDrawSTW, /* B3D_FACE_STW */ b3dDrawSTWRGB, /* B3D_FACE_STW | B3D_FACE_RGB */ b3dDrawSTWA, /* B3D_FACE_STW | B3D_FACE_ALPHA */ b3dDrawSTWARGB /* B3D_FACE_STW | B3D_FACE_RGB | B3D_FACE_ALPHA */};void b3dNoDraw(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ if(b3dDebug) b3dAbort("b3dNoDraw called!!");}void b3dDrawRGBFlat(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ struct b3dPixelColor { B3DPrimitiveColor color; } pv, *bits; int rValue, gValue, bValue; int deltaR, deltaG, deltaB; { B3DPrimitiveAttribute *attr = face->attributes; /* Ughh ... I''m having a sampling problem somewhere. In theory, the faces should be sampled *exactly* at integer values (the necessary offset should be done before) so that we always sample inside the triangle. For some reason that doesn''t quite work yet and that''s why here is the strange 0.5 offset and the awful lot of tests. At some time I''ll review this but for now I have more important things to do. */ double floatX = leftX; double floatY = yValue+0.5; if(b3dDebug) if(!!attr) b3dAbort("face has no RGB attributes"); SETUP_RGB; } bits = (struct b3dPixelColor *) currentState->spanBuffer; pv.redValue = (unsigned char) (rValue >> B3D_FixedToIntShift); pv.greenValue = (unsigned char) (gValue >> B3D_FixedToIntShift); pv.blueValue = (unsigned char) (bValue >> B3D_FixedToIntShift); pv.alphaValue = 255; while(leftX <= rightX) { bits[leftX++] = pv; }}void b3dDrawRGB(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ struct b3dPixelColor { B3DPrimitiveColor color; } pv, *bits; int rValue, gValue, bValue; int deltaR, deltaG, deltaB; int deltaX, pixelShift; { B3DPrimitiveAttribute *attr = face->attributes; /* Ughh ... I''m having a sampling problem somewhere. In theory, the faces should be sampled *exactly* at integer values (the necessary offset should be done before) so that we always sample inside the triangle. For some reason that doesn''t quite work yet and that''s why here is the strange 0.5 offset and the awful lot of tests. At some time I''ll review this but for now I have more important things to do. */ double floatX = leftX; double floatY = yValue+0.5; if(b3dDebug) if(!!attr) b3dAbort("face has no RGB attributes"); SETUP_RGB; } bits = (struct b3dPixelColor *) currentState->spanBuffer; pv.alphaValue = 255; /* Reduce the overhead of clamping by precomputing the deltas for each power of two step. A good question here is whether or not it is a good idea to do 2 pixels by this... */ deltaX = rightX - leftX + 1; /* Now do all the powers of two except the last one pixel */ /* Note: A smart compiler (== gcc) should unroll the following loop */ for(pixelShift= MAX_PIXEL_SHIFT; pixelShift> 0; pixelShift--) { int nPixels = 1 << pixelShift; /* Note: The ''if'' here is possible since we have dealt with huge polys above */ while(deltaX >= nPixels) { { /* Compute right most values of color interpolation */ int maxR = rValue + (deltaR << pixelShift); int maxG = gValue + (deltaG << pixelShift); int maxB = bValue + (deltaB << pixelShift); /* Clamp those guys */ CLAMP_RGB(maxR, maxG, maxB); /* And compute the actual delta */ deltaR = (maxR - rValue) >> pixelShift; deltaG = (maxG - gValue) >> pixelShift; deltaB = (maxB - bValue) >> pixelShift; } /* Do the inner loop */ { int n = nPixels; while(n--) { pv.redValue = (unsigned char) (rValue >> B3D_FixedToIntShift); pv.greenValue = (unsigned char) (gValue >> B3D_FixedToIntShift); pv.blueValue = (unsigned char) (bValue >> B3D_FixedToIntShift); bits[leftX++] = pv; rValue += deltaR; gValue += deltaG; bValue += deltaB; } } /* Finally, adjust the number of pixels left */ deltaX -= nPixels; } } /* The last pixel is done separately */ if(deltaX) { pv.redValue = (unsigned char) (rValue >> B3D_FixedToIntShift); pv.greenValue = (unsigned char) (gValue >> B3D_FixedToIntShift); pv.blueValue = (unsigned char) (bValue >> B3D_FixedToIntShift); bits[leftX++] = pv; }}void b3dDrawSTWRGB(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ struct b3dPixelColor { B3DPrimitiveColor color; } pv, *bits, *tex00, *tex10, *tex01, *tex11; double sValue, tValue, wValue, sDelta, tDelta, wDelta, oneOverW; int rValue, gValue, bValue; int deltaR, deltaG, deltaB; int tr, tg, tb, ta; int fixedLeftS, fixedRightS, fixedLeftT, fixedRightT, fixedDeltaS, fixedDeltaT; int deltaX, pixelShift; B3DTexture *texture = face->texture; INIT_MULTBL; if(!!texture || 0) { /* If no texture simply draw RGB */ b3dDrawRGB(leftX, rightX, yValue, face); return; } if(texture->depth < 16 && (texture->cmSize < (1 << texture->depth))) return; /* Colormap not installed */ { B3DPrimitiveAttribute *attr = face->attributes; /* See above */ double floatX = leftX; double floatY = yValue+0.5; if(b3dDebug) if(!!attr) b3dAbort("face has no RGB attributes"); SETUP_RGB; SETUP_STW; } tr = tg = tb = ta = 255; bits = (struct b3dPixelColor *) currentState->spanBuffer; pv.alphaValue = 255; /* VERY Experimental: Reduce the overhead of clamping as well as division by W by precomputing the deltas for each power of two step */ deltaX = rightX - leftX + 1; if(wValue) oneOverW = 1.0 / wValue; else oneOverW = 0.0; fixedLeftS = (int) (sValue * oneOverW * (texture->width << B3D_IntToFixedShift)); fixedLeftT = (int) (tValue * oneOverW * (texture->height << B3D_IntToFixedShift)); for(pixelShift = MAX_PIXEL_SHIFT; pixelShift > 0; pixelShift--) { int nPixels = 1 << pixelShift; while(deltaX >= nPixels) { { /* Compute right most values of color interpolation */ int maxR = rValue + (deltaR << pixelShift); int maxG = gValue + (deltaG << pixelShift); int maxB = bValue + (deltaB << pixelShift); /* Clamp those guys */ CLAMP_RGB(maxR, maxG, maxB); /* And compute the actual delta */ deltaR = (maxR - rValue) >> pixelShift; deltaG = (maxG - gValue) >> pixelShift; deltaB = (maxB - bValue) >> pixelShift; } /* Compute the RIGHT s/t values (the left ones are kept from the last loop) */ wValue += wDelta * nPixels; sValue += sDelta * nPixels; tValue += tDelta * nPixels; if(wValue) oneOverW = 1.0 / wValue; else oneOverW = 0.0; fixedRightS = (int) (sValue * oneOverW * (texture->width << B3D_IntToFixedShift)); fixedDeltaS = (fixedRightS - fixedLeftS) >> pixelShift; fixedRightT = (int) (tValue * oneOverW * (texture->height << B3D_IntToFixedShift)); fixedDeltaT = (fixedRightT - fixedLeftT) >> pixelShift; /* Do the inner loop */ { int n = nPixels; while(n--) { /* Do the texture load ... hmm ... there should be a way to avoid loading the texture on each pixel... On the other hand, the texture load does not seem too expensive if compared with the texture interpolation. */ LOAD_4_RGB_TEXEL_32(fixedLeftS, fixedLeftT, texture); /* Do the interpolation based on tex00, tex01, tex10, tex11. THIS seems to be one of the real bottlenecks here... */ INTERPOLATE_RGB_TEXEL(fixedLeftS, fixedLeftT);#if USE_MULTBL pv.redValue = (unsigned char) (MULTBL[rValue >> (B3D_FixedToIntShift+4)][tr]); pv.greenValue = (unsigned char) (MULTBL[gValue >> (B3D_FixedToIntShift+4)][tg]); pv.blueValue = (unsigned char) (MULTBL[bValue >> (B3D_FixedToIntShift+4)][tb]);#else pv.redValue = (unsigned char) ((tr * rValue) >> (B3D_FixedToIntShift + 8)); pv.greenValue = (unsigned char) ((tg * gValue) >> (B3D_FixedToIntShift + 8)); pv.blueValue = (unsigned char) ((tb * bValue) >> (B3D_FixedToIntShift + 8));#endif bits[leftX++] = pv; rValue += deltaR; gValue += deltaG; bValue += deltaB; fixedLeftS += fixedDeltaS; fixedLeftT += fixedDeltaT; } } /* Finally, adjust the number of pixels left and update s/t */ deltaX -= nPixels; fixedLeftS = fixedRightS; fixedLeftT = fixedRightT; } } /* The last pixel is done separately */ if(deltaX) { /* Do the texture load */ LOAD_4_RGB_TEXEL_32(fixedLeftS, fixedLeftT, texture); /* Do the interpolation */ INTERPOLATE_RGB_TEXEL(fixedLeftS, fixedLeftT);#if USE_MULTBL pv.redValue = (unsigned char) (MULTBL[rValue >> (B3D_FixedToIntShift+4)][tr]); pv.greenValue = (unsigned char) (MULTBL[gValue >> (B3D_FixedToIntShift+4)][tg]); pv.blueValue = (unsigned char) (MULTBL[bValue >> (B3D_FixedToIntShift+4)][tb]);#else pv.redValue = (unsigned char) ((tr * rValue) >> (B3D_FixedToIntShift + 8)); pv.greenValue = (unsigned char) ((tg * gValue) >> (B3D_FixedToIntShift + 8)); pv.blueValue = (unsigned char) ((tb * bValue) >> (B3D_FixedToIntShift + 8));#endif bits[leftX++] = pv; }}void b3dDrawSTWARGB(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ /* not yet implemented */}void b3dDrawRGBA(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ /* not yet implemented */}void b3dDrawSTW(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ /* not yet implemented */}void b3dDrawSTWA(int leftX, int rightX, int yValue, B3DPrimitiveFace *face){ /* not yet implemented */}'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/18/1999 18:27'!b3dHeaderH^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3d.h* CONTENT: Main include file** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#ifndef __B3D_H#define __B3D_H#ifdef DEBUG#define b3dDebug 1#else#define b3dDebug 0#endif#define b3dDoStats 1/* primary include file */#include "b3dTypes.h"#include "b3dAlloc.h"typedef int (*b3dDrawBufferFunction) (int leftX, int rightX, int yValue);typedef struct B3DRasterizerState { /* The three sources for allocating temporary rasterizer objects */ B3DFaceAllocList *faceAlloc; B3DEdgeAllocList *edgeAlloc; B3DAttrAllocList *attrAlloc; /* The active edge table */ B3DActiveEdgeTable *aet; /* The list for newly added edges */ B3DPrimitiveEdgeList *addedEdges; /* The fill list */ B3DFillList *fillList; /* The input objects for the rasterizer */ int nObjects; B3DPrimitiveObject **objects; /* The input textures for the rasterizer */ int nTextures; B3DTexture *textures; /* Length and location of span buffer to use */ int spanSize; unsigned int *spanBuffer; /* Function to call on drawing the output buffer */ b3dDrawBufferFunction spanDrawer;} B3DRasterizerState;extern B3DRasterizerState *currentState;/* from b3dInit.c */int b3dInitializeEdgeAllocator(void* base, int length);int b3dInitializeFaceAllocator(void* base, int length);int b3dInitializeAttrAllocator(void* base, int length);int b3dInitializeAET(void* base, int length);int b3dInitializeEdgeList(void* base, int length);int b3dInitializeFillList(void* base, int length);void b3dSetupObjects(B3DRasterizerState *state);int b3dAddPolygonObject(void *objBase, int objLength, int objFlags, int textureIndex, B3DPrimitiveVertex *vtxPointer, int nVertices, B3DPrimitiveViewport *vp);int b3dAddIndexedQuadObject(void *objBase, int objLength, int objFlags, int textureIndex, B3DPrimitiveVertex *vtxPointer, int nVertices, B3DInputQuad *quadPtr, int nQuads, B3DPrimitiveViewport *vp);int b3dAddIndexedTriangleObject(void *objBase, int objLength, int objFlags, int textureIndex, B3DPrimitiveVertex *vtxPointer, int nVertices, B3DInputFace *facePtr, int nFaces, B3DPrimitiveViewport *vp);int b3dLoadTexture(B3DTexture *texture, int width, int height, int depth, unsigned int *bits, int cmSize, unsigned int *colormap);/* from b3dRemap.c */int b3dValidateAndRemapState(B3DRasterizerState *state);/* from b3dDraw.c */typedef void (*b3dPixelDrawer) (int leftX, int rightX, int yValue, B3DPrimitiveFace *face);extern b3dPixelDrawer B3D_FILL_FUNCTIONS[];/* from b3dMain.c */void b3dAbort(char *msg);int b3dMainLoop(B3DRasterizerState *state, int stopReason);#endif'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/21/1999 00:31'!b3dInitC^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dInit.c* CONTENT: Initialization functions for the B3D rasterizer** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#include <string.h>#include "b3d.h"#define b3dCompensateWindowPos 1/* helpers */#define rasterPosX rasterPos[0]#define rasterPosY rasterPos[1]#define rasterPosZ rasterPos[2]#define rasterPosW rasterPos[3]#define windowPosX windowPos[0]#define windowPosY windowPos[1]#define texCoordS texCoord[0]#define texCoordT texCoord[1]/*************************************************************//*************************************************************//*************************************************************/int b3dInitializeEdgeAllocator(void* base, int length){ B3DEdgeAllocList *list = (B3DEdgeAllocList*) base; if(length < sizeof(B3DEdgeAllocList)) return B3D_GENERIC_ERROR; list->magic = B3D_EDGE_ALLOC_MAGIC; list->This = base; list->max = (length - sizeof(B3DEdgeAllocList)) / sizeof(B3DPrimitiveEdge) + 1; list->size = 0; list->nFree = list->max; list->firstFree = NULL; return B3D_NO_ERROR;}int b3dInitializeFaceAllocator(void* base, int length){ B3DFaceAllocList *list = (B3DFaceAllocList*) base; if(length < sizeof(B3DFaceAllocList)) return B3D_GENERIC_ERROR; list->magic = B3D_FACE_ALLOC_MAGIC; list->This = base; list->max = (length - sizeof(B3DFaceAllocList)) / sizeof(B3DPrimitiveFace) + 1; list->size = 0; list->nFree = list->max; list->firstFree = NULL; return B3D_NO_ERROR;}int b3dInitializeAttrAllocator(void* base, int length){ B3DAttrAllocList *list = (B3DAttrAllocList*) base; if(length < sizeof(B3DAttrAllocList)) return B3D_GENERIC_ERROR; list->magic = B3D_ATTR_ALLOC_MAGIC; list->This = base; list->max = (length - sizeof(B3DAttrAllocList)) / sizeof(B3DPrimitiveAttribute) + 1; list->size = 0; list->nFree = list->max; list->firstFree = NULL; return B3D_NO_ERROR;}int b3dInitializeEdgeList(void* base, int length){ B3DPrimitiveEdgeList *list = (B3DPrimitiveEdgeList*) base; if(length < sizeof(B3DPrimitiveEdgeList)) return B3D_GENERIC_ERROR; list->magic = B3D_EDGE_LIST_MAGIC; list->This = base; list->max = (length - sizeof(B3DPrimitiveEdgeList)) / sizeof(B3DPrimitiveEdge*) + 1; list->size = 0; return B3D_NO_ERROR;}int b3dInitializeAET(void* base, int length){ B3DActiveEdgeTable *aet = (B3DActiveEdgeTable *) base; if(length < sizeof(B3DActiveEdgeTable)) return B3D_GENERIC_ERROR; aet->magic = B3D_AET_MAGIC; aet->This = base; aet->max = (length - sizeof(B3DActiveEdgeTable)) / sizeof(B3DPrimitiveEdge*) + 1; aet->size = 0; aet->leftEdge = aet->rightEdge = NULL; aet->lastIntersection = &aet->tempEdge0; aet->nextIntersection = &aet->tempEdge1; return B3D_NO_ERROR;}int b3dInitializeFillList(void* base, int length){ B3DFillList *list = (B3DFillList*) base; if(length < sizeof(B3DFillList)) return B3D_GENERIC_ERROR; list->magic = B3D_FILL_LIST_MAGIC; list->This = base; list->firstFace = list->lastFace = NULL; return B3D_NO_ERROR;}/*************************************************************//*************************************************************//*************************************************************//* b3dMapObjectVertices: Map all the vertices of the given object into the designated viewport.*/void b3dMapObjectVertices(B3DPrimitiveObject *obj, B3DPrimitiveViewport *vp){ double xScale, yScale, xOfs, yOfs; int minX, minY, maxX, maxY; double minZ, maxZ; B3DPrimitiveVertex *vtx; int i; xOfs = (vp->x0 + vp->x1) * 0.5 - 0.5; yOfs = (vp->y0 + vp->y1) * 0.5 - 0.5; xScale = (vp->x1 - vp->x0) * 0.5; yScale = (vp->y1 - vp->y0) * -0.5; minX = minY = maxX = maxY = 0x7FFFFFFF; minZ = maxZ = 0.0; vtx = obj->vertices + 1; for(i=1; i < obj->nVertices; i++, vtx++) { double x,y,z,w; int scaledX, scaledY; w = vtx->rasterPosW; if(w) w = 1.0 / w; x = vtx->rasterPosX * w * xScale + xOfs; y = vtx->rasterPosY * w * yScale + yOfs; z = vtx->rasterPosZ * w; if(!!b3dCompensateWindowPos) { vtx->rasterPosX = (float)x; vtx->rasterPosY = (float)y; } vtx->rasterPosZ = (float)z; vtx->rasterPosW = (float)w; scaledX = (int) (x * B3D_FloatToFixed); scaledY = (int) (y * B3D_FloatToFixed); vtx->windowPosX = scaledX; vtx->windowPosY = scaledY; if(b3dCompensateWindowPos) { vtx->rasterPosX = (float) (scaledX * B3D_FixedToFloat); vtx->rasterPosY = (float) (scaledY * B3D_FixedToFloat); } /* Update min/max */ if(i == 1) { minX = maxX = scaledX; minY = maxY = scaledY; minZ = maxZ = z; } else { if(scaledX < minX) minX = scaledX; else if(scaledX > maxX) maxX = scaledX; if(scaledY < minY) minY = scaledY; else if(scaledY > maxY) maxY = scaledY; if(z < minZ) minZ = z; else if(z > maxZ) maxZ = z; } } obj->minX = minX >> B3D_FixedToIntShift; obj->maxX = maxX >> B3D_FixedToIntShift; obj->minY = minY >> B3D_FixedToIntShift; obj->maxY = maxY >> B3D_FixedToIntShift; obj->minZ = (float)minZ; obj->maxZ = (float)maxZ;}/* b3dSetupVertexOrder: Setup the ordering of the vertices in each face so that v0 sorts before v1 sorts before v2. Gather some stats on how much locally sorted and invalid faces the object includes.*/void b3dSetupVertexOrder(B3DPrimitiveObject *obj){ B3DInputFace *face; int i, nSorted, nInvalid; B3DPrimitiveVertex *vtx, *lastTopVtx, *newTopVtx; face = obj->faces; vtx = obj->vertices; nSorted = nInvalid = 0; lastTopVtx = NULL; for(i=0;i<obj->nFaces; i++,face++) { B3DPrimitiveVertex *vtx0, *vtx1, *vtx2; int idx0, idx1, idx2; idx0 = face->i0; idx1 = face->i1; idx2 = face->i2; if(0 == (idx0 && idx1 && idx2)) { nInvalid++; continue; } vtx0 = vtx + idx0; vtx1 = vtx + idx1; vtx2 = vtx + idx2; if(vtxSortsBefore(vtx0,vtx1)) { if(vtxSortsBefore(vtx1,vtx2)) { face->i0 = idx0; face->i1 = idx1; face->i2 = idx2; } else if(vtxSortsBefore(vtx0,vtx2)) { face->i0 = idx0; face->i1 = idx2; face->i2 = idx1; } else { face->i0 = idx2; face->i1 = idx0; face->i2 = idx1; } } else if(vtxSortsBefore(vtx0, vtx2)) { face->i0 = idx1; face->i1 = idx0; face->i2 = idx2; } else if(vtxSortsBefore(vtx1, vtx2)) { face->i0 = idx1; face->i1 = idx2; face->i2 = idx0; } else { face->i0 = idx2; face->i1 = idx1; face->i2 = idx0; } if(b3dDebug) { vtx0 = vtx + face->i0; vtx1 = vtx + face->i1; vtx2 = vtx + face->i2; if( !!vtxSortsBefore(vtx0, vtx1) || !!vtxSortsBefore(vtx0, vtx2) || !!vtxSortsBefore(vtx1, vtx2)) b3dAbort("Vertex order problem"); } /* Experimental: Try to estimate how many faces are already sorted. */ newTopVtx = vtx + face->i0; if(lastTopVtx) if(vtxSortsBefore(lastTopVtx, newTopVtx)) nSorted++; lastTopVtx = newTopVtx; } obj->nSortedFaces = nSorted; obj->nInvalidFaces = nInvalid;}/* b3dSortInitialFaces: Sort the faces of the given object according to the given sort order. Note: It is assumed that the vertex order of the faces has been setup before.*/void b3dQuickSortInitialFaces(B3DPrimitiveObject *obj, int i, int j){ B3DInputFace tmp, *faces = obj->faces; int ij, k, l, n; B3DPrimitiveVertex *di, *dj, *dij, *tt, *vtx = obj->vertices; n = j + 1 - i; if(n <= 1) return; /* Sort di,dj. */ di = vtx + faces[i].i0; dj = vtx + faces[j].i0; if(!!vtxSortsBefore(di,dj)) { tmp = faces[i]; faces[i] = faces[j]; faces[j] = tmp; tt = di; di = dj; dj = tt; } if(n <= 2) return; /* More than two elements. */ ij = (i+j) >> 1; /* ij is the midpoint of i and j. */ dij = vtx + faces[ij].i0; /* Sort di,dij,dj. Make dij be their median. */ if(vtxSortsBefore(di, dij)) {/* i.e. should di precede dij? */ if(!!vtxSortsBefore(dij, dj)) {/* i.e., should dij precede dj?*/ tmp = faces[j]; faces[j] = faces[ij]; faces[ij] = tmp; dij = dj; } } else { /* i.e. di should come after dij */ tmp = faces[i]; faces[i] = faces[ij]; faces[ij] = tmp; dij = di; } if(n <= 3) return; /* More than three elements. Find k>i and l<j such that dk,dij,dl are in reverse order. Swap k and l. Repeat this procedure until k and l pass each other.*/ k = i; l = j; while(k <= l) { while(k <= --l && (vtxSortsBefore(dij, vtx + faces[l].i0))); while(++k <= l && (vtxSortsBefore(vtx + faces[k].i0, dij))); if(k <= l) { tmp = faces[k]; faces[k] = faces[l]; faces[l] = tmp; } } /* Now l<k (either 1 or 2 less), and di through dl are all less than or equal to dk through dj. Sort those two segments. */ b3dQuickSortInitialFaces(obj, i, l); b3dQuickSortInitialFaces(obj, k, j);}/*************************************************************//*************************************************************//*************************************************************/void b3dValidateObjectFaces(B3DPrimitiveObject *obj){ int i; B3DInputFace *face,*nextFace; face = obj->faces; nextFace = face + 1; for(i=1; i < obj->nFaces; i++, face++, nextFace++) { if(!!vtxSortsBefore(obj->vertices + face->i0, obj->vertices + nextFace->i0)) b3dAbort("Face sorting problem"); }}#define InitObject(obj, objBase, objFlags, textureIndex) \ obj = (B3DPrimitiveObject*) objBase; \ obj->magic = B3D_PRIMITIVE_OBJECT_MAGIC; \ obj->This = objBase; \ obj->start = 0; \ obj->next = NULL; \ obj->flags = objFlags; \ obj->textureIndex = textureIndex; \ obj->texture = NULL;#define InitVertex(vtx) \ (vtx)->rasterPosX = \ (vtx)->rasterPosY = \ (vtx)->rasterPosZ = \ (vtx)->rasterPosW = \ (vtx)->texCoordS = \ (vtx)->texCoordT = (float) 0.0;\ (vtx)->windowPosX = \ (vtx)->windowPosY = 0x7FFFFFFF; \ (vtx)->cc.pixelValue32 = 0;/* b3dAddIndexedTriangleObject: Create a new primitive object.*/int b3dAddIndexedTriangleObject(void *objBase, int objLength, int objFlags, int textureIndex, B3DPrimitiveVertex *vtxPointer, int nVertices, B3DInputFace *facePtr, int nFaces, B3DPrimitiveViewport *vp){ B3DPrimitiveObject *obj; int sizeNeeded; sizeNeeded = sizeof(B3DPrimitiveObject) + sizeof(B3DPrimitiveVertex) * (nVertices+1) + sizeof(B3DInputFace) * nFaces; if(!!objBase || objLength < sizeNeeded) return B3D_GENERIC_ERROR; InitObject(obj, objBase, objFlags, textureIndex); /* copy in the primitive vertices (starting immediately after the prim object) */ obj->nVertices = nVertices+1; /* For one-based indexing leave one more entry */ obj->vertices = (B3DPrimitiveVertex*) (obj + 1); memcpy(obj->vertices+1, vtxPointer, nVertices * sizeof(B3DPrimitiveVertex)); /* copy in the input faces (starting after the vertices) */ obj->nFaces = nFaces; obj->faces = (B3DInputFace*) (obj->vertices + obj->nVertices); memcpy(obj->faces, facePtr, nFaces * sizeof(B3DInputFace)); /* Initialize the first vertex with something useful */ InitVertex(obj->vertices); b3dMapObjectVertices(obj, vp); b3dSetupVertexOrder(obj); b3dQuickSortInitialFaces(obj,0,obj->nFaces-1); if(b3dDebug) b3dValidateObjectFaces(obj); return B3D_NO_ERROR;}/* b3dAddIndexedQuadObject: Create a new primitive object.*/int b3dAddIndexedQuadObject(void *objBase, int objLength, int objFlags, int textureIndex, B3DPrimitiveVertex *vtxPointer, int nVertices, B3DInputQuad *quadPtr, int nQuads, B3DPrimitiveViewport *vp){ B3DPrimitiveObject *obj; int sizeNeeded; sizeNeeded = sizeof(B3DPrimitiveObject) + sizeof(B3DPrimitiveVertex) * (nVertices+1) + sizeof(B3DInputFace) * nQuads * 2; if(!!objBase || objLength < sizeNeeded) return B3D_GENERIC_ERROR; InitObject(obj, objBase, objFlags, textureIndex); /* copy in the primitive vertices (starting immediately after the prim object) */ obj->nVertices = nVertices+1; /* For one-based indexing leave one more entry */ obj->vertices = (B3DPrimitiveVertex*) (obj + 1); memcpy(obj->vertices+1, vtxPointer, nVertices * sizeof(B3DPrimitiveVertex)); /* copy in the input faces (starting after the vertices) */ obj->nFaces = nQuads * 2; obj->faces = (B3DInputFace*) (obj->vertices + obj->nVertices); { int i, nFaces = obj->nFaces; B3DInputQuad *src = quadPtr; B3DInputFace *dst = obj->faces; for(i=0; i < nFaces; i++, src++) { dst->i0 = src->i0; dst->i1 = src->i1; dst->i2 = src->i2; dst++; dst->i0 = src->i2; dst->i1 = src->i3; dst->i2 = src->i0; dst++; } } /* Initialize the first vertex with something useful */ InitVertex(obj->vertices); b3dMapObjectVertices(obj, vp); b3dSetupVertexOrder(obj); b3dQuickSortInitialFaces(obj,0,obj->nFaces-1); if(b3dDebug) b3dValidateObjectFaces(obj); return B3D_NO_ERROR;}/* b3dAddPolygonObject: Create a new primitive object.*/int b3dAddPolygonObject(void *objBase, int objLength, int objFlags, int textureIndex, B3DPrimitiveVertex *vtxPointer, int nVertices, B3DPrimitiveViewport *vp){ B3DPrimitiveObject *obj; int sizeNeeded; sizeNeeded = sizeof(B3DPrimitiveObject) + sizeof(B3DPrimitiveVertex) * (nVertices+1) + sizeof(B3DInputFace) * (nVertices - 2); if(!!objBase || objLength < sizeNeeded) return B3D_GENERIC_ERROR; InitObject(obj, objBase, objFlags, textureIndex); /* copy in the primitive vertices (starting immediately after the prim object) */ obj->nVertices = nVertices+1; /* For one-based indexing leave one more entry */ obj->vertices = (B3DPrimitiveVertex*) (obj + 1); memcpy(obj->vertices+1, vtxPointer, nVertices * sizeof(B3DPrimitiveVertex)); /* copy in the input faces (starting after the vertices) */ obj->nFaces = nVertices - 2; obj->faces = (B3DInputFace*) (obj->vertices + obj->nVertices); { B3DInputFace *dst = obj->faces; int i, nFaces = obj->nFaces; for(i=0; i < nFaces; i++, dst++) { dst->i0 = 1; dst->i1 = 2+i; dst->i2 = 3+i; } } /* Initialize the first vertex with something useful */ InitVertex(obj->vertices); b3dMapObjectVertices(obj, vp); b3dSetupVertexOrder(obj); b3dQuickSortInitialFaces(obj,0,obj->nFaces-1); if(b3dDebug) b3dValidateObjectFaces(obj); return B3D_NO_ERROR;}/*************************************************************//*************************************************************//*************************************************************/int b3dLoadTexture(B3DTexture *texture, int width, int height, int depth, unsigned int *bits, int cmSize, unsigned int *colormap){ int nBits; if(width < 1 || height < 1) return B3D_GENERIC_ERROR; if(depth !!= 32) return B3D_GENERIC_ERROR; if(depth !!= 8 && depth !!= 16 && depth !!= 32) return B3D_GENERIC_ERROR; if(depth == 8 && cmSize < 256) return B3D_GENERIC_ERROR; texture->width = width; texture->height = height; texture->depth = depth; texture->data = bits; texture->cmSize = cmSize; texture->colormap = colormap; texture->rowLength = width; nBits = 1; while((1 << nBits) < width) nBits++; if((1<<nBits) == width) { texture->sMask = (1<<nBits) - 1; texture->sShift = nBits; } else { texture->sMask = texture->sShift = 0; } while((1 << nBits) < height) nBits++; if((1<<nBits) == height) { texture->tMask = (1<<nBits) - 1; texture->tShift = nBits; } else { texture->tMask = texture->tShift = 0; } return B3D_NO_ERROR;}/*************************************************************//*************************************************************//*************************************************************//* b3dQuickSortObjects: Sort the objects in the given range.*/void b3dQuickSortObjects(B3DPrimitiveObject **array, int i, int j){ int ij, k, l, n; B3DPrimitiveObject *di, *dj, *dij, *tmp; n = j + 1 - i; if(n <= 1) return; /* Sort di,dj. */ di = array[i]; dj = array[j]; if(!!objSortsBefore(di,dj)) { tmp = array[i]; array[i] = array[j]; array[j] = tmp; tmp = di; di = dj; dj = tmp; } if(n <= 2) return; /* More than two elements. */ ij = (i+j) >> 1; /* ij is the midpoint of i and j. */ dij = array[ij]; /* Sort di,dij,dj. Make dij be their median. */ if(objSortsBefore(di, dij)) {/* i.e. should di precede dij? */ if(!!objSortsBefore(dij, dj)) {/* i.e., should dij precede dj?*/ tmp = array[j]; array[j] = array[ij]; array[ij] = tmp; dij = dj; } } else { /* i.e. di should come after dij */ tmp = array[i]; array[i] = array[ij]; array[ij] = tmp; dij = di; } if(n <= 3) return; /* More than three elements. Find k>i and l<j such that dk,dij,dl are in reverse order. Swap k and l. Repeat this procedure until k and l pass each other.*/ k = i; l = j; while(k <= l) { while(k <= --l && (objSortsBefore(dij, array[l]))); while(++k <= l && (objSortsBefore(array[k], dij))); if(k <= l) { tmp = array[k]; array[k] = array[l]; array[l] = tmp; } } /* Now l<k (either 1 or 2 less), and di through dl are all less than or equal to dk through dj. Sort those two segments. */ b3dQuickSortObjects(array, i, l); b3dQuickSortObjects(array, k, j);}/* b3dSetupObjects: Sort the objects and create a linked list between the objects.*/void b3dSetupObjects(B3DRasterizerState *state){ int i, textureIndex, nTextures = state->nTextures, nObjects = state->nObjects; B3DPrimitiveObject *obj, **objects = state->objects; B3DTexture *textures = state->textures; b3dQuickSortObjects(objects, 0, nObjects-1); for(i=0; i<nObjects; i++) { if(b3dDebug && i) { if(!!objSortsBefore(objects[i-1], objects[i])) b3dAbort("Object sorting problem"); } obj = objects[i]; obj->flags &= ~(B3D_OBJECT_ACTIVE | B3D_OBJECT_DONE); obj->start = 0; /*-- Note: The following is important --*/ obj->nFaces -= obj->nInvalidFaces; if(!!obj->nFaces) break; /*-- End --*/ textureIndex = obj->textureIndex - 1; if(textureIndex >= 0 && textureIndex < nTextures) { obj->texture = textures + textureIndex; obj->flags |= B3D_FACE_STW; } else obj->texture = NULL; obj->next = NULL; if(i) { objects[i-1]->next = obj; obj->prev = objects[i-1]; } }}'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/18/1999 08:33'!b3dMainC^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dMain.c* CONTENT: Main rasterizer body** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#include <stdio.h> /* printf() */#include <stdlib.h> /* exit() */#include <assert.h> /* assert() */#include "b3d.h"#ifndef NULL#define NULL ((void*)0)#endif#ifdef B3D_PROFILEunsigned int b3dObjSetupTime;unsigned int b3dMapObjectTime;unsigned int b3dVertexOrderTime;unsigned int b3dSortFaceTime;#endif/* helpers */#define rasterPosX rasterPos[0]#define rasterPosY rasterPos[1]#define rasterPosZ rasterPos[2]#define rasterPosW rasterPos[3]#define windowPosX windowPos[0]#define windowPosY windowPos[1]#define texCoordS texCoord[0]#define texCoordT texCoord[1]#define redValue cc.color[RED_INDEX]#define greenValue cc.color[GREEN_INDEX]#define blueValue cc.color[BLUE_INDEX]#define alphaValue cc.color[ALPHA_INDEX]/* globals */B3DRasterizerState *currentState;B3DActiveEdgeTable *aet;B3DPrimitiveEdgeList *addedEdges;B3DEdgeAllocList *edgeAlloc;B3DFaceAllocList *faceAlloc;B3DAttrAllocList *attrAlloc;int nFaces = 0;int maxFaces = 0;int maxEdges = 0;/*************************************************************//*************************************************************//*************************************************************/void b3dAbort(char *msg){ printf(msg); exit(-1);}void b3dValidateEdgeOrder(B3DPrimitiveEdgeList *list){ int i; if(list->size) if(list->data[0]->leftFace == list->data[0]->rightFace) { b3dAbort("Left face == right face"); } for(i=1; i<list->size; i++) { if(list->data[i-1]->xValue > list->data[i]->xValue) { b3dAbort("Edge list is broken"); } if(list->data[i]->leftFace == list->data[i]->rightFace) { b3dAbort("Left face == right face"); } }}void b3dValidateAETOrder(B3DActiveEdgeTable *list){ int i; if(list->size) if(list->data[0]->leftFace == list->data[0]->rightFace) { b3dAbort("Left face == right face"); } for(i=1; i<list->size; i++) { if(list->data[i-1]->xValue > list->data[i]->xValue) { b3dAbort("Edge list is broken"); } if(list->data[i]->leftFace == list->data[i]->rightFace) { b3dAbort("Left face == right face"); } }}/*************************************************************//*************************************************************//*************************************************************//* b3dInitializeFace: Allocate a new primitive face based on the given vertices. Do the necessary initial setup, but don''t set up any drawing attributes yet. Return the newly created face. NOTE: May cause allocation of one face!!*/B3DPrimitiveFace *b3dInitializeFace(B3DPrimitiveVertex *v0, B3DPrimitiveVertex *v1, B3DPrimitiveVertex *v2, B3DTexture *texture, int attrFlags){ B3DPrimitiveFace *face; /* Compute major and minor reference edges */ { float majorDx = v2->rasterPosX - v0->rasterPosX; float majorDy = v2->rasterPosY - v0->rasterPosY; float minorDx = v1->rasterPosX - v0->rasterPosX; float minorDy = v1->rasterPosY - v0->rasterPosY; float area = (majorDx * minorDy) - (minorDx * majorDy); if(area > -0.001 && area < 0.001) return NULL; /* Now that we know the face is valid, do the actual allocation */ b3dAllocFace(faceAlloc, face); if(b3dDebug) if(!!face) b3dAbort("Face allocation failed"); face->v0 = v0; face->v1 = v1; face->v2 = v2; face->leftEdge = NULL; face->rightEdge = NULL; face->attributes = NULL; face->oneOverArea = (float) (1.0 / area); face->majorDx = majorDx; face->majorDy = majorDy; face->minorDx = minorDx; face->minorDy = minorDy; face->texture = texture; face->flags |= attrFlags & (B3D_ATTR_MASK << B3D_ATTR_SHIFT); { /* Compute dzdx and dzdy */ float majorDz = v2->rasterPosZ - v0->rasterPosZ; float minorDz = v1->rasterPosZ - v0->rasterPosZ; face->dzdx = face->oneOverArea * ((majorDz * minorDy) - (minorDz * majorDy)); face->dzdy = face->oneOverArea * ((majorDx * minorDz) - (minorDx * majorDz)); } } {/* Compute minZ/maxZ */ float z0 = v0->rasterPosZ; float z1 = v1->rasterPosZ; float z2 = v2->rasterPosZ; if(z0 <= z1) { if(z1 <= z2) { face->minZ = z0; face->maxZ = z2; } else if(z0 <= z2) { face->minZ = z0; face->maxZ = z1; } else { face->minZ = z2; face->maxZ = z1; } } else if(z2 <= z1) { face->minZ = z2; face->maxZ = z0; } else if(z0 <= z2) { face->minZ = z1; face->maxZ = z0; } else { face->minZ = z1; face->maxZ = z0; } } /* End of minZ/maxZ */ return face;}/* b3dInitializePass2: Do a second initialization pass if the face is known to be visible.*/int b3dInitializePass2(B3DPrimitiveFace *face){ double majorDv, minorDv, baseValue; double dvdx, dvdy; B3DPrimitiveAttribute *attr; B3DPrimitiveVertex *v0 = face->v0; B3DPrimitiveVertex *v1 = face->v1; B3DPrimitiveVertex *v2 = face->v2; { int ok; b3dAllocAttrib(attrAlloc, face, ok); if(!!ok) return 0; /* NOT initalized */ } attr = face->attributes; assert(attr); if(face->flags & B3D_FACE_RGB) { /* Setup RGB interpolation */ majorDv = v2->redValue - v0->redValue; minorDv = v1->redValue - v0->redValue; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) v0->redValue; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; majorDv = v2->greenValue - v0->greenValue; minorDv = v1->greenValue - v0->greenValue; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) v0->greenValue; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; majorDv = v2->blueValue - v0->blueValue; minorDv = v1->blueValue - v0->blueValue; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) v0->blueValue; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; } if(face->flags & B3D_FACE_ALPHA) { /* Setup alpha interpolation */ majorDv = v2->alphaValue - v0->alphaValue; minorDv = v1->alphaValue - v0->alphaValue; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) v0->alphaValue; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; } if(face->flags & B3D_FACE_STW) { /* Setup texture coordinate interpolation */ double w0 = v0->rasterPosW; double w1 = v1->rasterPosW; double w2 = v2->rasterPosW; majorDv = w2 - w0; minorDv = w1 - w0; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) w0; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; baseValue = v0->texCoordS * w0; majorDv = (v2->texCoordS * w2) - baseValue; minorDv = (v1->texCoordS * w1) - baseValue; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) baseValue; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; baseValue = v0->texCoordT * w0; majorDv = (v2->texCoordT * w2) - baseValue; minorDv = (v1->texCoordT * w1) - baseValue; dvdx = face->oneOverArea * ((majorDv * face->minorDy) - (minorDv * face->majorDy)); dvdy = face->oneOverArea * ((minorDv * face->majorDx) - (majorDv * face->minorDx)); attr->value = (float) baseValue; attr->dvdx = (float) dvdx; attr->dvdy = (float) dvdy; attr = attr->next; } face->flags |= B3D_FACE_INITIALIZED; return 1;}/* b3dInitializeEdge: Initialize the incremental values of the given edge.*//* INLINE b3dInitializeEdge(edge) */void b3dInitializeEdge(B3DPrimitiveEdge *edge){ assert(edge); assert(edge->nLines); edge->xValue = edge->v0->windowPosX; edge->zValue = edge->v0->rasterPosZ; if(edge->nLines > 1) { edge->xIncrement = (edge->v1->windowPosX - edge->v0->windowPosX) / edge->nLines; edge->zIncrement = (edge->v1->rasterPosZ - edge->v0->rasterPosZ) / (float) edge->nLines; } else { edge->xIncrement = (edge->v1->windowPosX - edge->v0->windowPosX); edge->zIncrement = (edge->v1->rasterPosZ - edge->v0->rasterPosZ); }}/* --INLINE-- *//*************************************************************//*************************************************************//*************************************************************//* b3dFirstIndexForInserting: Return the first possible index for inserting an edge with the given x value.*/int b3dFirstIndexForInserting(B3DPrimitiveEdgeList *list, int xValue){ int low, high, index; low = 0; high = list->size-1; while(low <= high) { index = (low + high) >> 1; if(list->data[index]->xValue <= xValue) low = index+1; else high = index-1; } index = low; while(index > 0 && (list->data[index-1]->xValue) == xValue) index--; return index;}/* b3dAddEdgeBeforeIndex: Insert the edge to the list before the given index.*//* INLINE b3dAddEdgeBeforeIndex(list, edge, index) */void b3dAddEdgeBeforeIndex(B3DPrimitiveEdgeList *list, B3DPrimitiveEdge *edge, int index){ int i; if(b3dDebug) if(list->size == list->max) b3dAbort("No more space for adding edges"); assert( (list->size == index) || (list->data[index]->xValue >= edge->xValue)); for(i=list->size-1; i >= index; i--) list->data[i+1] = list->data[i]; list->data[index] = edge; list->size++;}/* --INLINE-- *//* b3d2AddEdgesBeforeIndex: Insert the two edge to the list before the given index.*//* INLINE b3dAdd2EdgesBeforeIndex(list, edge1, edge2, index) */void b3dAdd2EdgesBeforeIndex(B3DPrimitiveEdgeList *list, B3DPrimitiveEdge *edge1, B3DPrimitiveEdge *edge2, int index){ int i; if(b3dDebug) if(list->size+1 >= list->max) b3dAbort("No more space for adding edges"); assert( edge1->xValue == edge2->xValue); assert( (list->size == index) || (list->data[index]->xValue >= edge1->xValue)); for(i=list->size-1; i >= index; i--) list->data[i+2] = list->data[i]; list->data[index] = edge1; list->data[index+1] = edge2; list->size += 2;}/* --INLINE-- *//* b3dAdjustFaceEdges: Assign left and right edges to the given face.*//* INLINE b3dAdjustFaceEdges(face, edge1, edge2) */void b3dAdjustFaceEdges(B3DPrimitiveFace *face, B3DPrimitiveEdge *edge1, B3DPrimitiveEdge *edge2){ assert(face); assert(edge1); assert(edge2); if(edge1->xValue == edge2->xValue) { if(edge1->xIncrement <= edge2->xIncrement) { face->leftEdge = edge1; face->rightEdge = edge2; } else { face->leftEdge = edge2; face->rightEdge = edge1; } } else { if(edge1->xValue <= edge2->xValue) { face->leftEdge = edge1; face->rightEdge = edge2; } else { face->leftEdge = edge2; face->rightEdge = edge1; } }}/* --INLINE-- *//* b3dAddLowerEdgeFromFace: Add a new lower edge from the given face. NOTE: oldEdge may be NULL!! NOTE: May cause allocation of one edge!!*/B3DPrimitiveEdge *b3dAddLowerEdgeFromFace(B3DPrimitiveFace *face, B3DPrimitiveEdge *oldEdge){ B3DPrimitiveVertex *v0 = face->v0; B3DPrimitiveVertex *v1 = face->v1; B3DPrimitiveVertex *v2 = face->v2; int xValue = v1->windowPosX; int index; /* Search the list of added edges to merge the edges from the face */ index = b3dFirstIndexForInserting(addedEdges, xValue); for(;index<addedEdges->size; index++) { B3DPrimitiveEdge *edge = addedEdges->data[index]; if(edge->xValue !!= xValue) break; if(edge->rightFace) continue; if((edge->v0 == v1 && edge->v1 == v2) || /* The simple test*/ /* The complex test */ (edge->v0->windowPosX == v1->windowPosX && edge->v0->windowPosY == v1->windowPosY && edge->v0->rasterPosZ == v1->rasterPosZ && edge->v1->windowPosX == v2->windowPosX && edge->v1->windowPosY == v2->windowPosY && edge->v1->rasterPosZ == v2->rasterPosZ)) { /* Found the edge */ if(face->leftEdge == oldEdge) face->leftEdge = edge; else face->rightEdge = edge; edge->rightFace = face; return edge; } } /* Need to create a new edge. NOTE: Index already points to the right insertion point. */ { B3DPrimitiveEdge *minorEdge; int nLines = (v2->windowPosY >> B3D_FixedToIntShift) - (v1->windowPosY >> B3D_FixedToIntShift); if(!!nLines) return NULL; /* Edge is horizontal */ b3dAllocEdge(edgeAlloc, minorEdge); if(b3dDebug) if(!!minorEdge) b3dAbort("Edge allocation failed"); minorEdge->v0 = v1; minorEdge->v1 = v2; minorEdge->nLines = nLines; minorEdge->leftFace = face; minorEdge->rightFace = NULL; if(face->leftEdge == oldEdge) face->leftEdge = minorEdge; else face->rightEdge = minorEdge; b3dInitializeEdge(minorEdge); b3dAddEdgeBeforeIndex(addedEdges, minorEdge, index); return minorEdge; } /* NOT REACHED */}/* b3dAddEdgesFromFace: Add the two new edges from the given primitive face. NOTE: May cause allocation of two edges (but not three)!!*/void b3dAddEdgesFromFace(B3DPrimitiveFace *face, int yValue){ int needMajor = 1; int needMinor = 1; B3DPrimitiveEdge *majorEdge = NULL; B3DPrimitiveEdge *minorEdge = NULL; B3DPrimitiveVertex *v0 = face->v0; B3DPrimitiveVertex *v1 = face->v1; B3DPrimitiveVertex *v2 = face->v2; int xValue = v0->windowPosX; int index; /* Search the list of added edges to merge the edges from the face */ index = b3dFirstIndexForInserting(addedEdges, xValue); for(;index<addedEdges->size; index++) { B3DPrimitiveEdge *edge = addedEdges->data[index]; if(edge->xValue !!= xValue) break; if(edge->rightFace) continue; if(edge->v0 !!= v0 && (edge->v0->windowPosY !!= v0->windowPosY || edge->v0->rasterPosZ !!= v0->rasterPosZ)) continue; /* If we come to this point the edge might be usable for merging the face */ if(needMajor && /* Test only if major edge is needed */ (edge->v1 == v2 || /* Simple test */ /* A more complex test */ (edge->v1->windowPosX == v2->windowPosX && edge->v1->windowPosY == v2->windowPosY && edge->v1->rasterPosZ == v2->rasterPosZ))) { /* Yepp. That''s the new major */ majorEdge = edge; majorEdge->rightFace = face; majorEdge->flags |= B3D_EDGE_RIGHT_MAJOR; if(b3dDoStats) nFaces++; if(!!needMinor) { b3dAdjustFaceEdges(face, majorEdge, minorEdge); return; /* done */ } needMajor = 0; } else if(needMinor && /* Test only if minor edge is needed */ (edge->v1 == v1 || /* Simple test */ /* A more complex test */ (edge->v1->windowPosX == v1->windowPosX && edge->v1->windowPosY == v1->windowPosY && edge->v1->rasterPosZ == v1->rasterPosZ))) { /* Yepp. That''s the new minor */ minorEdge = edge; minorEdge->rightFace = face; minorEdge->flags |= B3D_EDGE_CONTINUE_RIGHT; if(!!needMajor) { b3dAdjustFaceEdges(face, majorEdge, minorEdge); return; /* done */ } needMinor = 0; } } /* Need to create new edges. Note: index already points to the right insertion point in addedEdges */ if(needMajor) { int nLines = (v2->windowPosY >> B3D_FixedToIntShift) - (v0->windowPosY >> B3D_FixedToIntShift); if(!!nLines) { /* The major edge is horizontal. */ b3dFreeFace(faceAlloc, face); return; } b3dAllocEdge(edgeAlloc, majorEdge); if(b3dDebug) if(!!majorEdge) b3dAbort("Edge allocation failed"); majorEdge->v0 = v0; majorEdge->v1 = v2; majorEdge->nLines = nLines; majorEdge->leftFace = face; majorEdge->rightFace = NULL; majorEdge->flags |= B3D_EDGE_LEFT_MAJOR; b3dInitializeEdge(majorEdge); if(b3dDoStats) nFaces++; } if(needMinor) { int nLines = (v1->windowPosY >> B3D_FixedToIntShift) - (v0->windowPosY >> B3D_FixedToIntShift); if(!!nLines) { /* Note: If the (upper) minor edge is horizontal, use the lower one. Note: The lower edge cannot be horizontal if the major edge isn''t */ if(needMajor) { b3dAddEdgeBeforeIndex(addedEdges, majorEdge, index); } minorEdge = b3dAddLowerEdgeFromFace(face,NULL); if(b3dDebug) if(!!minorEdge || minorEdge->nLines == 0) b3dAbort("minor edge is horizontal"); b3dAdjustFaceEdges(face, majorEdge, minorEdge); return; } b3dAllocEdge(edgeAlloc, minorEdge); if(b3dDebug) if(!!minorEdge) b3dAbort("Edge allocation failed"); minorEdge->v0 = v0; minorEdge->v1 = v1; minorEdge->nLines = nLines; minorEdge->leftFace = face; minorEdge->rightFace = NULL; minorEdge->flags |= B3D_EDGE_CONTINUE_LEFT; b3dInitializeEdge(minorEdge); } /* Add the newly created edges to addedEdges */ if(needMinor && needMajor) { b3dAdd2EdgesBeforeIndex(addedEdges, majorEdge, minorEdge, index); } else if(needMajor) { b3dAddEdgeBeforeIndex(addedEdges, majorEdge, index); } else { b3dAddEdgeBeforeIndex(addedEdges, minorEdge, index); } b3dAdjustFaceEdges(face, majorEdge, minorEdge);}/* b3dRemoveAETEdge: Remove the given edge from the AET. NOTE: May cause allocation of two edges!!*//* INLINE b3dRemoveAETEdge(aet, edge, yValue, aetPos) */void b3dRemoveAETEdge(B3DActiveEdgeTable *aet, B3DPrimitiveEdge *edge, int yValue, int aetPos){ /* Remove edge and add lower edges if necessary */ int j; B3DPrimitiveEdge **aetData = aet->data; assert(aetData[aetPos] == edge); if(b3dDebug) if( (edge->v1->windowPosY >> B3D_FixedToIntShift) !!= yValue ) b3dAbort("Edge exceeds range"); /* Remove the edge and adjust the stuff */ for(j=aetPos+1; j < aet->size; j++) aetData[j-1] = aetData[j]; aet->size--; /* Add new lower edges */ if(edge->flags & B3D_EDGE_CONTINUE_LEFT) { b3dAddLowerEdgeFromFace(edge->leftFace, edge); } if(edge->flags & B3D_EDGE_CONTINUE_RIGHT) { b3dAddLowerEdgeFromFace(edge->rightFace, edge); } if(edge->flags & B3D_EDGE_LEFT_MAJOR) { /* Free left face */ b3dFreeAttrib(attrAlloc, edge->leftFace); b3dFreeFace(faceAlloc, edge->leftFace); if(b3dDoStats) nFaces--; } if(edge->flags & B3D_EDGE_RIGHT_MAJOR) { /* Free right face */ b3dFreeAttrib(attrAlloc, edge->rightFace); b3dFreeFace(faceAlloc, edge->rightFace); if(b3dDoStats) nFaces--; } /* And free old edge */ b3dFreeEdge(edgeAlloc, edge);}/* --INLINE-- *//* b3dMergeAETEdgesFrom: Merge the edges from the given source into the AET.*/void b3dMergeAETEdgesFrom(B3DActiveEdgeTable *aet, B3DPrimitiveEdgeList *src){ int srcIndex, aetIndex, outIndex, i; B3DPrimitiveEdge *srcEdge, *aetEdge; assert(aet); assert(src); assert(src->size); assert(aet->size + src->size <= aet->max); if(!!aet->size) { for(i=0; i<src->size; i++) aet->data[i] = src->data[i]; aet->size += src->size; return; } /* Merge the input by stepping backwards through the aet and checking each edge */ outIndex = aet->size + src->size - 1; srcIndex = src->size-1; aetIndex = aet->size-1; srcEdge = src->data[srcIndex]; aetEdge = aet->data[aetIndex]; aet->size += src->size; while(1) { if(srcEdge->xValue >= aetEdge->xValue) { /* output srcEdge */ aet->data[outIndex--] = srcEdge; if(!!srcIndex--) return; srcEdge = src->data[srcIndex]; } else { /* output aetEdge */ aet->data[outIndex--] = aetEdge; if(!!aetIndex--) { for(i=0; i <= srcIndex; i++) aet->data[i] = src->data[i]; return; } aetEdge = aet->data[aetIndex]; } }}/* INLINE b3dAdvanceAETEdge(edge, aetData, aetStart) */void b3dAdvanceAETEdge(B3DPrimitiveEdge *edge, B3DPrimitiveEdge **aetData, int aetStart){ /* Advance to next scan line */ edge->zValue += edge->zIncrement; edge->xValue += edge->xIncrement; /* Check if AET sort order is okay */ if(aetStart && aetData[aetStart-1]->xValue > edge->xValue) { /* Must resort rightEdge */ int xValue = edge->xValue; int j = aetStart; /* Move the edge left */ while(j>0 && aetData[j-1]->xValue > xValue) { aetData[j] = aetData[j-1]; j--; } aetData[j] = edge; }}/* --INLINE-- *//*************************************************************//*************************************************************//*************************************************************/#ifdef DEBUGdouble zValueAt(B3DPrimitiveFace *face, double xValue, double yValue){ return (face->v0->rasterPosZ + (((double)xValue - face->v0->rasterPosX) * face->dzdx) + (((double)yValue - face->v0->rasterPosY) * face->dzdy));}#else#define zValueAt(face, xValue, yValue) \ ((face)->v0->rasterPosZ + \ (((double)(xValue) - (face)->v0->rasterPosX) * (face)->dzdx) +\ (((double)(yValue) - (face)->v0->rasterPosY) * (face)->dzdy))#endif/*************************************************************//*************************************************************//*************************************************************/int b3dComputeIntersection(B3DPrimitiveFace *frontFace, B3DPrimitiveFace *backFace, int yValue, int errorValue){ double dx1 = frontFace->rightEdge->xValue - frontFace->leftEdge->xValue; double dz1 = frontFace->rightEdge->zValue - frontFace->leftEdge->zValue; double dx2 = backFace->rightEdge->xValue - backFace->leftEdge->xValue; double dz2 = backFace->rightEdge->zValue - backFace->leftEdge->zValue; double px = backFace->leftEdge->xValue - frontFace->leftEdge->xValue; double pz = backFace->leftEdge->zValue - frontFace->leftEdge->zValue; double det = (dx1 * dz2) - (dx2 * dz1); if(det == 0.0) return errorValue; { double det2 = ((px * dz2) - (pz * dx2)) / det; return frontFace->leftEdge->xValue + (int)(dx1 * det2); } /* not reached */}/* b3dCheckIntersectionOfFaces: Compute the possible intersection of frontFace and backFace. Store the result in nextIntersection if it is before any other intersection. Return true if other intersections tests should be performed, false otherwise.*/int b3dCheckIntersectionOfFaces(B3DPrimitiveFace *frontFace, B3DPrimitiveFace *backFace, int yValue, B3DPrimitiveEdge *leftEdge, B3DPrimitiveEdge *nextIntersection){ double frontZ, backZ; int xValue, rightX; /* Check if the backFace is completely behind the front face */ if(backFace->minZ >= frontFace->maxZ) return 0; /* abort */ /* Check if front and back face share any edges */ if(frontFace->leftEdge == backFace->leftEdge) return 1; /* proceed */ if(frontFace->rightEdge == backFace->rightEdge) return 1; /* proceed */ /* Check if either front or back face are less than 1 pixel wide */ if( (frontFace->leftEdge->xValue >> B3D_FixedToIntShift) == (frontFace->rightEdge->xValue >> B3D_FixedToIntShift)) return 0; /* abort */ if( (backFace->leftEdge->xValue >> B3D_FixedToIntShift) == (backFace->rightEdge->xValue >> B3D_FixedToIntShift)) return 1; /* proceed */ /* Choose the right x value of either front or back face, whichever is less (this is so we sample inside both faces) */ if(frontFace->rightEdge->xValue <= backFace->rightEdge->xValue) { rightX = frontFace->rightEdge->xValue; frontZ = frontFace->rightEdge->zValue; backZ = zValueAt(backFace, rightX * B3D_FixedToFloat, yValue); } else { rightX = backFace->rightEdge->xValue; backZ = backFace->rightEdge->zValue; frontZ = zValueAt(frontFace, rightX * B3D_FixedToFloat, yValue); } if(backZ < frontZ) { /* possible intersection found */ xValue = b3dComputeIntersection(frontFace, backFace, yValue, leftEdge->xValue); if(xValue > rightX) xValue = rightX; /* Ignore intersections at or before the leftEdge''s x value. Important. */ if((xValue >> B3D_FixedToIntShift) <= (leftEdge->xValue >> B3D_FixedToIntShift)) xValue = ((leftEdge->xValue >> B3D_FixedToIntShift) + 1) << B3D_IntToFixedShift; if(xValue < nextIntersection->xValue) { nextIntersection->xValue = xValue; nextIntersection->leftFace = frontFace; nextIntersection->rightFace = backFace; } } return 1;}/* b3dAdjustIntersections: Compute the possible intersections of the current front face with all active faces. Store the next intersection if any.*//* INLINE b3dAdjustIntersections(fillList, yValue, topEdge, nextIntersection) */void b3dAdjustIntersections(B3DFillList *fillList, int yValue, B3DPrimitiveEdge *topEdge, B3DPrimitiveEdge *nextIntersection){ B3DPrimitiveFace *frontFace = fillList->firstFace; if(frontFace) { B3DPrimitiveFace *backFace = frontFace->nextFace; int proceed = 1; while(backFace && proceed) { proceed = b3dCheckIntersectionOfFaces(frontFace, backFace, yValue, topEdge, nextIntersection); backFace = backFace->nextFace; } }}/* --INLINE-- *//*************************************************************//*************************************************************//*************************************************************/void b3dValidateFillList(B3DFillList *list){ B3DPrimitiveFace *firstFace = list->firstFace; B3DPrimitiveFace *lastFace = list->lastFace; B3DPrimitiveFace *face; if(!!firstFace && !!lastFace) return; if(firstFace->prevFace) b3dAbort("Bad fill list"); if(lastFace->nextFace) b3dAbort("Bad fill list"); face = firstFace; while(face !!= lastFace) face = face->nextFace; /* Validate sort order */ if(firstFace == lastFace) return; /* 0 or 1 element */ face = firstFace->nextFace; while(face->nextFace) { if(face->minZ > face->nextFace->minZ) b3dAbort("Fill list sorting problem"); face = face->nextFace; }}/* INLINE b3dAddFirstFill(fillList, aFace) */void b3dAddFirstFill(B3DFillList *fillList, B3DPrimitiveFace *aFace){ B3DPrimitiveFace *firstFace = fillList->firstFace; if(firstFace) firstFace->prevFace = aFace; else fillList->lastFace = aFace; aFace->nextFace = firstFace; aFace->prevFace = NULL; fillList->firstFace = aFace; if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//* INLINE b3dAddLastFill(fillList, aFace) */void b3dAddLastFill(B3DFillList *fillList, B3DPrimitiveFace *aFace){ B3DPrimitiveFace *lastFace = fillList->lastFace; if(lastFace) lastFace->nextFace = aFace; else fillList->firstFace = aFace; aFace->prevFace = lastFace; aFace->nextFace = NULL; fillList->lastFace = aFace; if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//* INLINE b3dRemoveFill(fillList, aFace) */void b3dRemoveFill(B3DFillList *fillList, B3DPrimitiveFace *aFace){ if(b3dDebug) b3dValidateFillList(fillList); if(aFace->prevFace) aFace->prevFace->nextFace = aFace->nextFace; else fillList->firstFace = aFace->nextFace; if(aFace->nextFace) aFace->nextFace->prevFace = aFace->prevFace; else fillList->lastFace = aFace->prevFace;}/* --INLINE-- *//* INLINE b3dInsertBeforeFill(fillList, aFace, otherFace) */void b3dInsertBeforeFill(B3DFillList *fillList, B3DPrimitiveFace *aFace, B3DPrimitiveFace *otherFace){ assert(otherFace !!= fillList->firstFace); aFace->nextFace = otherFace; aFace->prevFace = otherFace->prevFace; aFace->prevFace->nextFace = aFace; otherFace->prevFace = aFace; if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//* INLINE b3dAddFrontFill(fillList, aFace) */void b3dAddFrontFill(B3DFillList *fillList, B3DPrimitiveFace *aFace){ B3DPrimitiveFace *firstFace = fillList->firstFace; if(firstFace !!= fillList->lastFace) { /* Meaning that we must find the new position for the old front face */ B3DPrimitiveFace *backFace = firstFace->nextFace; float minZ = firstFace->minZ; while(backFace && backFace->minZ < minZ) backFace = backFace->nextFace; /* Insert firstFace before backFace */ if(firstFace->nextFace !!= backFace) { B3DPrimitiveFace *tempFace = firstFace; b3dRemoveFill(fillList, tempFace); if(backFace) { b3dInsertBeforeFill(fillList, tempFace, backFace); } else { b3dAddLastFill(fillList, tempFace); } } } b3dAddFirstFill(fillList, aFace); if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//* INLINE b3dAddBackFill(fillList, aFace) */void b3dAddBackFill(B3DFillList *fillList, B3DPrimitiveFace *aFace){ B3DPrimitiveFace *firstFace = fillList->firstFace; B3DPrimitiveFace *lastFace = fillList->lastFace; B3DPrimitiveFace *face; float minZ = aFace->minZ; assert(firstFace); if(firstFace == lastFace || minZ >= lastFace->minZ) { b3dAddLastFill(fillList, aFace); } else { /* Try an estimation on how to search */ if(minZ <= (firstFace->minZ + lastFace->minZ) * 0.5) { /* search front to back */ face = firstFace->nextFace; while(face->minZ < minZ) face = face->nextFace; } else { /* search back to front */ face = lastFace->prevFace; /* already checked if lastFace->minZ <= minZ */ while(face->minZ > minZ) face = face->prevFace; face = face->nextFace; } b3dInsertBeforeFill(fillList, aFace, face); } if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//* INLINE b3dCleanupFill(fillList) */void b3dCleanupFill(B3DFillList *fillList){ B3DPrimitiveFace *firstFace = fillList->firstFace; while(firstFace) { firstFace->flags ^= B3D_FACE_ACTIVE; firstFace = firstFace->nextFace; } fillList->firstFace = fillList->lastFace = NULL;}/* --INLINE-- */void b3dSearchForNewTopFill(B3DFillList *fillList, int scaledX, int yValue){ B3DPrimitiveFace *topFace = fillList->firstFace; if(b3dDebug) b3dValidateFillList(fillList); if(topFace) { /* only if there is any */ B3DPrimitiveFace *face = topFace->nextFace; double xValue = scaledX * B3D_FixedToFloat; double topZ = zValueAt(topFace, xValue, yValue); /* Note: since the list is ordered we need only to search until face->minZ >= topZ */ while(face && face->minZ <= topZ) { double faceZ = zValueAt(face, xValue, yValue); if(faceZ < topZ) { topZ = faceZ; topFace = face; } face = face->nextFace; } /* and move the guy to front */ b3dRemoveFill(fillList, topFace); b3dAddFrontFill(fillList, topFace); }}/* INLINE b3dToggleTopFills(fillList, edge, yValue) */void b3dToggleTopFills(B3DFillList *fillList, B3DPrimitiveEdge *edge, int yValue){ B3DPrimitiveFace *leftFace = edge->leftFace; B3DPrimitiveFace *rightFace = edge->rightFace; if(b3dDebug) b3dValidateFillList(fillList); assert(leftFace !!= rightFace); if(rightFace) { int xorMask = leftFace->flags ^ rightFace->flags; if(xorMask & B3D_FACE_ACTIVE) { if(leftFace->flags & B3D_FACE_ACTIVE) { b3dRemoveFill(fillList, leftFace); b3dAddFrontFill(fillList, rightFace); } else { b3dRemoveFill(fillList, rightFace); b3dAddFrontFill(fillList, leftFace); } } else { if(leftFace->flags & B3D_FACE_ACTIVE) { b3dRemoveFill(fillList, leftFace); b3dRemoveFill(fillList, rightFace); b3dSearchForNewTopFill(fillList, edge->xValue, yValue); } else { if(leftFace->dzdx <= rightFace->dzdx) { b3dAddFrontFill(fillList, leftFace); b3dAddBackFill(fillList, rightFace); } else { b3dAddFrontFill(fillList, rightFace); b3dAddBackFill(fillList, leftFace); } } } leftFace->flags ^= B3D_FACE_ACTIVE; rightFace->flags ^= B3D_FACE_ACTIVE; } else { if(leftFace->flags & B3D_FACE_ACTIVE) { b3dRemoveFill(fillList, leftFace); b3dSearchForNewTopFill(fillList, edge->xValue, yValue); } else { b3dAddFrontFill(fillList, leftFace); } leftFace->flags ^= B3D_FACE_ACTIVE; } if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//* INLINE b3dToggleBackFills(fillList, edge, yValue, nextIntersection) */void b3dToggleBackFills(B3DFillList *fillList, B3DPrimitiveEdge *edge, int yValue, B3DPrimitiveEdge *nextIntersection){ B3DPrimitiveFace *face = edge->leftFace; if(b3dDebug) b3dValidateFillList(fillList); if(face->flags & B3D_FACE_ACTIVE) { b3dRemoveFill(fillList, face); } else { b3dAddBackFill(fillList, face); b3dCheckIntersectionOfFaces(fillList->firstFace, face, yValue, edge, nextIntersection); } face->flags ^= B3D_FACE_ACTIVE; face = edge->rightFace; if(face) { if(face->flags & B3D_FACE_ACTIVE) { b3dRemoveFill(fillList, face); } else { b3dAddBackFill(fillList, face); b3dCheckIntersectionOfFaces(fillList->firstFace, face, yValue, edge, nextIntersection); } face->flags ^= B3D_FACE_ACTIVE; } if(b3dDebug) b3dValidateFillList(fillList);}/* --INLINE-- *//*************************************************************//*************************************************************//*************************************************************//* INLINE b3dClearSpanBuffer(aet) */void b3dClearSpanBuffer(B3DActiveEdgeTable *aet){ int i, leftX, rightX; unsigned int *buffer = currentState->spanBuffer; if(aet->size && buffer) { leftX = aet->data[0]->xValue >> B3D_FixedToIntShift; rightX = aet->data[aet->size-1]->xValue >> B3D_FixedToIntShift; if(leftX < 0) leftX = 0; if(rightX >= currentState->spanSize) rightX = currentState->spanSize-1; for(i=leftX;i<=rightX;i++) buffer[i] = 0; }}/* --INLINE-- *//* INLINE b3dDrawSpanBuffer(aet, yValue) */void b3dDrawSpanBuffer(B3DActiveEdgeTable *aet, int yValue){ int leftX, rightX; if(aet->size && currentState->spanDrawer) { leftX = aet->data[0]->xValue >> B3D_FixedToIntShift; rightX = aet->data[aet->size-1]->xValue >> B3D_FixedToIntShift; if(leftX < 0) leftX = 0; if(rightX > currentState->spanSize) rightX = currentState->spanSize; currentState->spanDrawer(leftX, rightX, yValue); }}/* --INLINE-- *//*************************************************************//*************************************************************//*************************************************************//* General failure */#define FAIL(reason,resume) { aet->yValue = yValue; return reason | resume; }#define PROCEED { yValue = aet->yValue; }/* Failure adding objects */#define FAIL_ADDING(reason) { obj->start = objStart; FAIL(reason, B3D_RESUME_ADDING) }#define PROCEED_ADDING { objStart = obj->start; PROCEED }/* Failure merging objects */#define FAIL_MERGING(reason) { FAIL(reason, B3D_RESUME_MERGING); }#define PROCEED_MERGING { PROCEED }/* Failure during paint */#define FAIL_PAINTING(reason) { aet->start = aetStart; aet->leftEdge = leftEdge; aet->rightEdge = rightEdge; FAIL(reason, B3D_RESUME_PAINTING) }#define PROCEED_PAINTING(reason) { aetStart = aet->start; leftEdge = aet->leftEdge; rightEdge = aet->rightEdge; PROCEED }#define FAIL_UPDATING(reason)int b3dMainLoop(B3DRasterizerState *state, int stopReason){ B3DPrimitiveObject *activeStart, *passiveStart; int yValue, nextObjY, nextEdgeY; B3DFillList *fillList; B3DPrimitiveEdge *lastIntersection, *nextIntersection; if(!!state) return B3D_GENERIC_ERROR; if(!!state->nObjects) return B3D_NO_ERROR; if(b3dValidateAndRemapState(state) !!= B3D_NO_ERROR) return B3D_GENERIC_ERROR; if(stopReason == B3D_NO_ERROR) b3dSetupObjects(state); if(b3dDebug) { /* check the sort order of objects */ int i; for(i=2; i<state->nObjects;i++) if(!!objSortsBefore(state->objects[i-1], state->objects[i])) b3dAbort("Objects not sorted"); } currentState = state; faceAlloc = state->faceAlloc; edgeAlloc = state->edgeAlloc; attrAlloc = state->attrAlloc; addedEdges = state->addedEdges; fillList = state->fillList; aet = state->aet; nextIntersection = aet->nextIntersection; lastIntersection = aet->lastIntersection; if(b3dDoStats) nFaces = 0; if(stopReason == B3D_NO_ERROR) { activeStart = passiveStart = state->objects[0]; yValue = nextEdgeY = nextObjY = passiveStart->minY; } else { int resumeCode; resumeCode = stopReason & B3D_RESUME_MASK; if(resumeCode == B3D_RESUME_ADDING ) goto RESUME_ADDING; if(resumeCode == B3D_RESUME_MERGING ) goto RESUME_MERGING; if(resumeCode == B3D_RESUME_PAINTING) goto RESUME_PAINTING; if(resumeCode == B3D_RESUME_UPDATING) goto RESUME_UPDATING; return B3D_GENERIC_ERROR; } /**** BEGIN MAINLOOP ****/ while(activeStart || passiveStart || aet->size) {RESUME_ADDING: /* STEP 1: Add new objects if necessary */ if(yValue == nextObjY) { nextEdgeY = nextObjY; while(passiveStart && passiveStart->minY == nextObjY) { passiveStart->flags |= B3D_OBJECT_ACTIVE; passiveStart = passiveStart->next; } if(passiveStart) nextObjY = passiveStart->minY; else nextObjY = 99999; } /* End of adding objects */ /* STEP 2: Add new edges if necessary */ if(yValue == nextEdgeY) { B3DPrimitiveObject *obj = activeStart; int scaledY = (yValue+1) << B3D_IntToFixedShift; nextEdgeY = nextObjY << B3D_IntToFixedShift; while(obj !!= passiveStart) { B3DInputFace *objFaces = obj->faces; B3DPrimitiveVertex *objVtx = obj->vertices; int objStart = obj->start; int objSize = obj->nFaces; int tempY; assert(obj->flags & B3D_OBJECT_ACTIVE); while(objStart < objSize && ((tempY = objVtx[objFaces[objStart].i0].windowPosY) < scaledY)) { /* add edges from face at objFaces[objStart] */ B3DInputFace *inputFace = objFaces + objStart; B3DPrimitiveFace *face; /* NOTE: If any of the following fails, we can re-enter the main loop later on. */ if(faceAlloc->nFree == 0) FAIL_ADDING(B3D_NO_MORE_FACES); if(edgeAlloc->nFree < 2) FAIL_ADDING(B3D_NO_MORE_EDGES); if(addedEdges->size+2 > addedEdges->max) FAIL_ADDING(B3D_NO_MORE_ADDED); /* Allocate a new face and do the initial setup */ face = b3dInitializeFace(objVtx + inputFace->i0, objVtx + inputFace->i1, objVtx + inputFace->i2, obj->texture, obj->flags); if(face) { b3dAddEdgesFromFace(face, yValue); } objStart++; } obj->start = objStart; if(objStart !!= objSize) { if(tempY < nextEdgeY) nextEdgeY = tempY; } else { /* Unlink obj from activeStart list */ obj->flags |= B3D_OBJECT_DONE; if(obj == activeStart) { activeStart = obj->next; } else { obj->prev->next = obj->next; } } obj = obj->next; } nextEdgeY >>= B3D_FixedToIntShift; } /* End of adding edges */ /* STEP 3: Merge all newly added edges from addedList into the AET */ if(addedEdges->size) {RESUME_MERGING: if(b3dDebug) b3dValidateEdgeOrder(addedEdges); /* NOTE: If the following fails, we can re-enter the main loop later on. */ if(aet->size + addedEdges->size > aet->max) FAIL_MERGING(B3D_NO_MORE_AET); b3dMergeAETEdgesFrom(aet, addedEdges); if(b3dDebug) { b3dValidateAETOrder(aet); } addedEdges->size = 0; /* reset added */ } /* End of merging edges */ /********** THIS IS THE CORE LOOP ********/ /* while(yValue < nextEdgeY && !!addedEdges->size && aet->size) { */ if(b3dDoStats) { /* Gather stats */ if(aet->size > maxEdges) maxEdges = aet->size; if(nFaces > maxFaces) maxFaces = nFaces; } /* STEP 4: Draw the current span */ /* STEP 4a: Clear the span buffer */ b3dClearSpanBuffer(aet); /* STEP 4b: Scan out the AET */ if(aet->size) { B3DPrimitiveEdge *leftEdge; B3DPrimitiveEdge *rightEdge; B3DPrimitiveEdge **aetData = aet->data; int aetStart = 1; int aetSize = aet->size; /* clean up old fills if any */ b3dCleanupFill(fillList); nextIntersection->xValue = B3D_MAX_X; leftEdge = aetData[0]; while(aetStart < aetSize) { /*-- Toggle the faces of the top edge (the left edge is always on top) --*/ if(leftEdge == lastIntersection) { /* Special case if this is a intersection edge */ assert(fillList->firstFace == leftEdge->leftFace); b3dRemoveFill(fillList, leftEdge->rightFace); b3dAddFrontFill(fillList, leftEdge->rightFace); } else { b3dToggleTopFills(fillList, leftEdge, yValue); } /*-- end of toggling top edge faces --*/ /* after getting a new top fill we must adjust intersections */ b3dAdjustIntersections(fillList, yValue, leftEdge, nextIntersection); /*-- search for the next top edge which will be the right edge --*/ assert(aetStart < aetSize); if(!!fillList->firstFace) rightEdge = aetData[aetStart++]; /* If no current top fill just use the next edge */ else while(aetStart < aetSize) { /* Search for the next top edge in the AET */ rightEdge = aetData[aetStart]; /* If we have an intersection use the intersection edge */ if(nextIntersection->xValue <= rightEdge->xValue) { rightEdge = nextIntersection; break; } aetStart++; /* Check if this edge is on top */ assert(fillList->firstFace); { double xValue = rightEdge->xValue * B3D_FixedToFloat; B3DPrimitiveFace *topFace = fillList->firstFace; if( rightEdge->leftFace == topFace || rightEdge->rightFace == topFace || rightEdge->zValue < zValueAt(topFace, xValue, yValue)) break; /* rightEdge is on top */ } /* If the edge is not on top toggle its (back) fills */ b3dToggleBackFills(fillList, rightEdge, yValue, nextIntersection); rightEdge = NULL; } /*-- end of search for next top edge --*/ /*-- Now do the drawing from leftEdge to rightEdge --*/ assert(rightEdge); if(fillList->firstFace) { /* Note: We fill *including* leftX and rightX */ int leftX = (leftEdge->xValue >> B3D_FixedToIntShift) + 1; int rightX = (rightEdge->xValue >> B3D_FixedToIntShift); B3DPrimitiveFace *topFace = fillList->firstFace; if(leftX < 0) leftX = 0; if(rightX >= currentState->spanSize) rightX = currentState->spanSize-1; if(leftX <= rightX) { /* Since we know now that some serious filling operation will happen, initialize the attributes of the face if this hasn''t been done before. */RESUME_PAINTING: if( (topFace->flags & B3D_FACE_INITIALIZED) == 0) { assert(topFace->attributes == NULL); if(!!b3dInitializePass2(topFace)) FAIL_PAINTING(B3D_NO_MORE_ATTRS); } /* And dispatch on the actual pixel drawers */ (*B3D_FILL_FUNCTIONS[(topFace->flags >> B3D_ATTR_SHIFT) & B3D_ATTR_MASK]) (leftX, rightX, yValue, topFace); } } /*-- End of drawing -- */ /* prepare for new top edge */ leftEdge = rightEdge; /* use a new intersection if necessary */ if(leftEdge == nextIntersection) { nextIntersection = lastIntersection; lastIntersection = leftEdge; } nextIntersection->xValue = B3D_MAX_X; } /* clean up old fills if any */ b3dCleanupFill(fillList); } /* STEP 4c: Display the pixels from the span buffer */ b3dDrawSpanBuffer(aet, yValue); /* STEP 5: Go to next y value and update AET entries */ yValue++; if(aet->size) { int aetStart = 0; int aetSize = aet->size; B3DPrimitiveEdge **aetData = aet->data; aetStart = 0; while(aetStart < aetSize) { B3DPrimitiveEdge *edge = aetData[aetStart]; if(--(edge->nLines)) { /* Advance to next scan line and resort edge */ b3dAdvanceAETEdge(edge, aetData, aetStart); aetStart++; } else { /* Remove edge and add lower edges if necessary */RESUME_UPDATING: if(edgeAlloc->nFree < 2) FAIL_UPDATING(B3D_NO_MORE_EDGES); if(addedEdges->size + 2 > addedEdges->max) FAIL_UPDATING(B3D_NO_MORE_ADDED); b3dRemoveAETEdge(aet, edge, yValue, aetStart); aetSize = aet->size; /* Do NOT advance aetStart here */ } } } /* End of AET update */ if(b3dDebug) { b3dValidateAETOrder(aet); } /*}*/ /******** END OF CORE LOOP ********/ } /**** END MAINLOOP ****/ return B3D_NO_ERROR;}'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'ar 4/18/1999 08:33'!b3dRemapC^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dRemap.c* CONTENT: Remapping functions for the B3D rasterizer** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#include "b3d.h"/* b3dRemapFaces: Remap all allocated faces using the given offsets*//* INLINE b3dRemapFaces(list, attrOffset, edgeOffset) */void b3dRemapFaces(B3DFaceAllocList *list, int attrOffset, int edgeOffset){ int i; for(i=0; i<list->size;i++) { B3DPrimitiveFace *face = list->data + i; if(face->flags & B3D_ALLOC_FLAG) { if(face->attributes) (char*)face->attributes += attrOffset; if(face->leftEdge) (char*)face->leftEdge += edgeOffset; if(face->rightEdge) (char*)face->rightEdge += edgeOffset; } }}/* --INLINE-- *//* b3dRemapEdges: Remap all allocated edges using the given offset*//* INLINE b3dRemapEdges(list, faceOffset) */void b3dRemapEdges(B3DEdgeAllocList *list, int faceOffset){ int i; for(i=0; i<list->size;i++) { B3DPrimitiveEdge *edge = list->data + i; if(edge->flags & B3D_ALLOC_FLAG) { if(edge->leftFace) (char*)edge->leftFace += faceOffset; if(edge->rightFace) (char*)edge->rightFace += faceOffset; } }}/* --INLINE-- *//* b3dRemapFills: Remap the fill list using the given offset*//* INLINE b3dRemapFills(fillList, offset) */void b3dRemapFills(B3DFillList *fillList, int offset){ B3DPrimitiveFace *temp; if(fillList->firstFace) (char*)fillList->firstFace += offset; if(fillList->lastFace) (char*)fillList->lastFace += offset; temp = fillList->firstFace; while(temp) { if(temp->nextFace) (char*)temp->nextFace += offset; if(temp->prevFace) (char*)temp->prevFace += offset; temp = temp->nextFace; }}/* --INLINE-- *//* b3dRemapEdgeList: Remap all edge pointers using the given offset*//* INLINE b3dRemapEdgeList(list, edgeOffset) */void b3dRemapEdgeList(B3DPrimitiveEdgeList *list, int edgeOffset){ int i; for(i=0; i<list->size;i++) { (char*) list->data[i] += edgeOffset; }}/* --INLINE-- *//* b3dRemapAET: Remap all edge pointers using the given offset*//* INLINE b3dRemapAET(list, edgeOffset, aetOffset, firstEdge, lastEdge) */void b3dRemapAET(B3DActiveEdgeTable *list, int edgeOffset, int aetOffset, void *firstEdge, void *lastEdge){ int i; if(edgeOffset) for(i=0; i<list->size;i++) (char*) list->data[i] += edgeOffset; if((void*)list->leftEdge >= firstEdge && (void*)list->leftEdge < lastEdge) (char*) list->leftEdge += edgeOffset; else if(list->leftEdge) (char*) list->leftEdge += aetOffset; if((void*)list->rightEdge >= firstEdge && (void*)list->rightEdge < lastEdge) (char*) list->rightEdge += edgeOffset; else if(list->rightEdge) (char*) list->rightEdge += aetOffset; if(aetOffset) { (char*) list->nextIntersection += aetOffset; (char*) list->lastIntersection += aetOffset; }}/* --INLINE-- *//* b3dRemapEdgeVertices: Remap all vertices in the specified range using the given offset*//* INLINE b3dRemapEdgeVertices(list, vtxOffset, firstVtx, lastVtx) */void b3dRemapEdgeVertices(B3DEdgeAllocList *list, int vtxOffset, void *firstVtx, void *lastVtx){ int i; for(i=0; i<list->size; i++) { B3DPrimitiveEdge *edge = list->data + i; if((edge->flags & B3D_ALLOC_FLAG) && ((void*)edge->v0 >= (void*)firstVtx) && ((void*)edge->v0 < (void*)lastVtx)) { (char*) edge->v0 += vtxOffset; (char*) edge->v1 += vtxOffset; } }}/* --INLINE-- *//* b3dRemapFaceVertices: Remap all vertices in the specified range using the given offset*//* INLINE b3dRemapFaceVertices(list, vtxOffset, firstVtx, lastVtx) */void b3dRemapFaceVertices(B3DFaceAllocList *list, int vtxOffset, void *firstVtx, void *lastVtx){ int i; for(i=0; i<list->size; i++) { B3DPrimitiveFace *face = list->data + i; if((face->flags & B3D_ALLOC_FLAG) && ((void*)face->v0 >= (void*)firstVtx) && ((void*)face->v0 < (void*)lastVtx)) { (char*) face->v0 += vtxOffset; (char*) face->v1 += vtxOffset; (char*) face->v2 += vtxOffset; } }}/* --INLINE-- *//* b3dRemapFaceFree: Remap all free faces using the given offset*//* INLINE b3dRemapFaceFree(list, faceOffset) */void b3dRemapFaceFree(B3DFaceAllocList *list, int faceOffset){ B3DPrimitiveFace *freeObj; if(list->firstFree) { (char*)list->firstFree += faceOffset; freeObj = list->firstFree; while(freeObj->nextFree) { (char*) freeObj->nextFree += faceOffset; freeObj = freeObj->nextFree; } }}/* --INLINE-- *//* b3dRemapEdgeFree: Remap all free edges using the given offset*//* INLINE b3dRemapEdgeFree(list, edgeOffset) */void b3dRemapEdgeFree(B3DEdgeAllocList *list, int edgeOffset){ B3DPrimitiveEdge *freeObj; if(list->firstFree) { (char*)list->firstFree += edgeOffset; freeObj = list->firstFree; while(freeObj->nextFree) { (char*) freeObj->nextFree += edgeOffset; freeObj = freeObj->nextFree; } }}/* --INLINE-- *//* b3dRemapAttrFree: Remap all free attributes using the given offset*//* INLINE b3dRemapAttrFree(list, attrOffset) */void b3dRemapAttributes(B3DAttrAllocList *list, int attrOffset){ int i; for(i=0; i < list->size; i++) { B3DPrimitiveAttribute *attr = list->data + i; if(attr->next) (char*) attr->next += attrOffset; }}/* --INLINE-- *//* b3dValidateAndRemapState: Validate the rasterizer state and remap the objects if necessary.*/int b3dValidateAndRemapState(B3DRasterizerState *state){ int faceOffset, edgeOffset, attrOffset, aetOffset, objOffset, i; B3DPrimitiveObject *obj; if(!!state) return B3D_GENERIC_ERROR; /* Check the magic numbers */ if(state->faceAlloc->magic !!= B3D_FACE_ALLOC_MAGIC) return B3D_MAGIC_ERROR; if(state->edgeAlloc->magic !!= B3D_EDGE_ALLOC_MAGIC) return B3D_MAGIC_ERROR; if(state->attrAlloc->magic !!= B3D_ATTR_ALLOC_MAGIC) return B3D_MAGIC_ERROR; if(state->aet->magic !!= B3D_AET_MAGIC) return B3D_MAGIC_ERROR; if(state->addedEdges->magic !!= B3D_EDGE_LIST_MAGIC) return B3D_MAGIC_ERROR; if(state->fillList->magic !!= B3D_FILL_LIST_MAGIC) return B3D_MAGIC_ERROR; /* Check if we need to relocate objects */ faceOffset = (int)state->faceAlloc - (int)state->faceAlloc->This; edgeOffset = (int)state->edgeAlloc - (int)state->edgeAlloc->This; attrOffset = (int)state->attrAlloc - (int)state->attrAlloc->This; aetOffset = (int)state->aet - (int)state->aet->This; /* remap faces */ if(attrOffset || edgeOffset) b3dRemapFaces(state->faceAlloc, attrOffset, edgeOffset); /* remap fills and edges */ if(faceOffset) { b3dRemapFills(state->fillList, faceOffset); b3dRemapEdges(state->edgeAlloc, faceOffset); b3dRemapFaceFree(state->faceAlloc, faceOffset); } /* Remap AET */ if(edgeOffset || aetOffset) { void *firstEdge = state->edgeAlloc->data; void *lastEdge = state->edgeAlloc->data + state->edgeAlloc->size; b3dRemapAET(state->aet, edgeOffset, aetOffset, firstEdge, lastEdge); } /* Remap addedEdges and edge free list*/ if(edgeOffset) { b3dRemapEdgeList(state->addedEdges, edgeOffset); b3dRemapEdgeFree(state->edgeAlloc, edgeOffset); } if(attrOffset) b3dRemapAttributes(state->attrAlloc, attrOffset); state->faceAlloc->This = (void*) state->faceAlloc; state->edgeAlloc->This = (void*) state->edgeAlloc; state->attrAlloc->This = (void*) state->attrAlloc; state->aet->This = (void*) state->aet; /* Remap any vertex pointers */ for(i=0; i<state->nObjects; i++) { obj = state->objects[i]; if(obj->magic !!= B3D_PRIMITIVE_OBJECT_MAGIC) return B3D_MAGIC_ERROR; objOffset = (int)obj - (int)obj->This; if(objOffset) { if((obj->flags & B3D_OBJECT_ACTIVE)) { B3DPrimitiveVertex *firstVtx = obj->vertices; B3DPrimitiveVertex *lastVtx = obj->vertices + obj->nVertices; b3dRemapFaceVertices(state->faceAlloc, objOffset, firstVtx, lastVtx); b3dRemapEdgeVertices(state->edgeAlloc, objOffset, firstVtx, lastVtx); } obj->vertices = (B3DPrimitiveVertex*) (obj + 1); obj->faces = (B3DInputFace*) (obj->vertices + obj->nVertices); } obj->This = (void*) obj; } return B3D_NO_ERROR;}'! !!B3DRasterizerPlugin class methodsFor: 'C source code' stamp: 'di 4/22/1999 09:14'!b3dTypesH^'/***************************************************************************** PROJECT: Balloon 3D Graphics Subsystem for Squeak* FILE: b3dTypes.h* CONTENT: Type declarations for the B3D rasterizer** AUTHOR: Andreas Raab (ar)* ADDRESS: Walt Disney Imagineering, Glendale, CA* EMAIL: andreasr@wdi.disney.com* RCSID: $Id$** NOTES:*******************************************************************************/#ifndef B3D_TYPES_H#define B3D_TYPES_H#ifndef NULL#define NULL ((void*)0)#endif/* Error constants */#define B3D_NO_ERROR 0/* Generic error */#define B3D_GENERIC_ERROR -1/* Bad magic number */#define B3D_MAGIC_ERROR -2/* Note: The error codes that allow resuming must be positive. They''ll be combined with the resume codes *//* no more space in edge allocation list */#define B3D_NO_MORE_EDGES 1/* no more space in face allocation list */#define B3D_NO_MORE_FACES 2/* no more space in attribute allocation list */#define B3D_NO_MORE_ATTRS 3/* no more space in active edge table */#define B3D_NO_MORE_AET 4/* no more space for added edges */#define B3D_NO_MORE_ADDED 5/* Resume codes */#define B3D_RESUME_MASK 0xF0000/* Resume adding objects/edges */#define B3D_RESUME_ADDING 0x10000/* Resume merging added edges */#define B3D_RESUME_MERGING 0x20000/* Resume painting faces */#define B3D_RESUME_PAINTING 0x40000/* Resume updating the AET */#define B3D_RESUME_UPDATING 0x80000/* Factor to convert from float to fixed pt */#define B3D_FloatToFixed 4096.0/* Factor to convert from fixed pt to float */#define B3D_FixedToFloat 0.000244140625/* Shift value to convert from integer to fixed pt */#define B3D_IntToFixedShift 12#define B3D_FixedToIntShift 12/* 0.5 in fixed pt representation */#define B3D_FixedHalf 2048/* Max. possible x value */#define B3D_MAX_X 0x7FFFFFFF/* Allocation flag: If this flag is not set then the nextFree pointer is valid */#define B3D_ALLOC_FLAG 1/************************ PrimitiveColor definition ************************/typedef unsigned char B3DPrimitiveColor[4];/* An ugly hack but I can''t find the global defs in CodeWarrior on the Mac */#ifndef LSB_FIRST #define MSB_FIRST#endif#ifndef MSB_FIRST #define RED_INDEX 0 #define GREEN_INDEX 1 #define BLUE_INDEX 2 #define ALPHA_INDEX 3#else #define ALPHA_INDEX 0 #define BLUE_INDEX 1 #define GREEN_INDEX 2 #define RED_INDEX 3#endif/************************ PrimitiveVertex definition ************************/typedef struct B3DPrimitiveVertex { float position[3]; float normal[3]; float texCoord[2]; float rasterPos[4]; union { int pixelValue32; B3DPrimitiveColor color; } cc; int clipFlags; int windowPos[2];} B3DPrimitiveVertex;/* sort order for primitive vertices */#define vtxSortsBefore(vtx1, vtx2) ( (vtx1)->windowPosY == (vtx2)->windowPosY ? (vtx1)->windowPosX <= (vtx2)->windowPosX : (vtx1)->windowPosY <= (vtx2)->windowPosY)/************************ InputFace definition ************************//* Note: The following is mainly so that we don''t need these weird int[3] declarations. */typedef struct B3DInputFace { int i0; int i1; int i2;} B3DInputFace;typedef struct B3DInputQuad { int i0; int i1; int i2; int i3;} B3DInputQuad;/************************ PrimitiveEdge definition ************************//* Edge flags: B3D_EDGE_CONTINUE_LEFT - continue with the lower edge of the left face B3D_EDGE_CONTINUE_RIGHT - continue with the lower edge of the right face B3D_EDGE_LEFT_MAJOR - edge is major edge for left face B3D_EDGE_RIGHT_MAJOR - edge is major edge for right face*/#define B3D_EDGE_CONTINUE_LEFT 0x10#define B3D_EDGE_CONTINUE_RIGHT 0x20#define B3D_EDGE_LEFT_MAJOR 0x40#define B3D_EDGE_RIGHT_MAJOR 0x80typedef struct B3DPrimitiveEdge { int flags; struct B3DPrimitiveEdge *nextFree; /* start/end of edge */ struct B3DPrimitiveVertex *v0; struct B3DPrimitiveVertex *v1; /* left/right face of edge (NOT meant literally) */ struct B3DPrimitiveFace *leftFace; struct B3DPrimitiveFace *rightFace; /* current x/z value */ int xValue; float zValue; /* x/z increment per scan line */ int xIncrement; float zIncrement; /* number of remaining scan lines */ int nLines;} B3DPrimitiveEdge;/* B3DPrimitiveEdgeList: A list of pointers to primitive edges */#define B3D_EDGE_LIST_MAGIC 0x45553342typedef struct B3DPrimitiveEdgeList { int magic; void *This; int start; int size; int max; B3DPrimitiveEdge *data[1];} B3DPrimitiveEdgeList;/* B3DActiveEdgeTable: The active edge table (basically a primitive edge table with few additional entries) */#define B3D_AET_MAGIC 0x41455420typedef struct B3DActiveEdgeTable { int magic; void *This; int start; int size; int max; /* Backups for proceeding after failure */ int yValue; B3DPrimitiveEdge *leftEdge; B3DPrimitiveEdge *rightEdge; B3DPrimitiveEdge *lastIntersection; B3DPrimitiveEdge *nextIntersection; /* That''s where lastIntersection and nextIntersection point to */ B3DPrimitiveEdge tempEdge0; B3DPrimitiveEdge tempEdge1; /* Actual data */ B3DPrimitiveEdge *data[1];} B3DActiveEdgeTable ;/************************ PrimitiveFace definition ************************//* Face flags: B3D_FACE_INITIALIZED - have the face attributes been initialized?!! B3D_FACE_ACTIVE - is the face currently in the fill list?!! B3D_FACE_HAS_ALPHA - can the face eventually be transparent?!! B3D_FACE_RGB - R,G,B interpolation values B3D_FACE_ALPHA - Alpha interpolation values B3D_FACE_STW - S,T,W interpolation values*/#define B3D_FACE_INITIALIZED 0x10#define B3D_FACE_ACTIVE 0x20#define B3D_FACE_HAS_ALPHA 0x40#define B3D_FACE_RGB 0x100#define B3D_FACE_ALPHA 0x200#define B3D_FACE_STW 0x400/* # of possible combinations AND maximum (e.g., R+G+B+A+S+T+W) of attribs *//* NOTE: This is a really ugly hack - I''ll have to fix that */#define B3D_MAX_ATTRIBUTES 8/* mask out the face attributes */#define B3D_ATTR_MASK 0x7/* shift for getting the attributes */#define B3D_ATTR_SHIFT 8typedef struct B3DPrimitiveFace { int flags; struct B3DPrimitiveFace *nextFree; /* The three vertices of the face */ struct B3DPrimitiveVertex *v0; struct B3DPrimitiveVertex *v1; struct B3DPrimitiveVertex *v2; /* The links for the (depth sorted) list of fills */ struct B3DPrimitiveFace *prevFace; struct B3DPrimitiveFace *nextFace; /* The left and right edge of the face (not taken too literally) */ struct B3DPrimitiveEdge *leftEdge; struct B3DPrimitiveEdge *rightEdge; /* The deltas for the major (e.g., v0-v2) and the first minor (e.g., v0-v1) edge */ float majorDx, majorDy; float minorDx, minorDy; /* The inverse area covered by (twice) the triangle */ float oneOverArea; /* Depth attributes are kept here since we almost always need ''em */ float minZ, maxZ; float dzdx, dzdy; /* The pointer to the texture */ struct B3DTexture *texture; /* The pointer to the extended (per face) interpolation values */ struct B3DPrimitiveAttribute *attributes;} B3DPrimitiveFace;/* B3DFillList: A (depth-sorted) list of primitive faces */#define B3D_FILL_LIST_MAGIC 0x46443342typedef struct B3DFillList { int magic; void *This; B3DPrimitiveFace *firstFace; B3DPrimitiveFace *lastFace;} B3DFillList;/************************ PrimitiveAttribute definition ************************/typedef struct B3DPrimitiveAttribute { /* Note: next is either nextFree or or nextUsed */ struct B3DPrimitiveAttribute *next; /* value at the face->v0 */ float value; /* value / dx derivative for face */ float dvdx; /* value / dy derivative for face */ float dvdy;} B3DPrimitiveAttribute;/************************ Texture definition ************************/#define B3D_TEXTURE_POWER_OF_2 0x10typedef struct B3DTexture { int width; int height; int depth; int rowLength; /* 32bit words per scan line */ int sMask; /* Nonzero for power of two width */ int sShift; int tMask; /* Nonzero for power of two height */ int tShift; int cmSize; /* length of color map */ unsigned int *colormap; unsigned int *data;} B3DTexture;/************************ PrimitiveViewport definition ************************/typedef struct B3DPrimitiveViewport { int x0, y0, x1, y1;} B3DPrimitiveViewport;/************************ PrimitiveObject definition ************************/#define B3D_OBJECT_ACTIVE 0x10#define B3D_OBJECT_DONE 0x20#define B3D_PRIMITIVE_OBJECT_MAGIC 0x4F443342typedef struct B3DPrimitiveObject { int magic; void *This; int __oop__; /* actual ST oop */ struct B3DPrimitiveObject *next; struct B3DPrimitiveObject *prev; int flags; int textureIndex; struct B3DTexture *texture; int minX, maxX, minY, maxY; float minZ, maxZ; int nSortedFaces; int nInvalidFaces; int start; int nFaces; B3DInputFace *faces; int nVertices; B3DPrimitiveVertex *vertices;} B3DPrimitiveObject;/* sort order for primitive objects */#define objSortsBefore(obj1, obj2) ( (obj1)->minY == (obj2)->minY ? (obj1)->minX <= (obj2)->minX : (obj1)->minY <= (obj2)->minY)#endif /* ifndef B3D_TYPES_H */'! !I represent a facade for all Balloon 3D operations. Clients should only interact with me, not with any of the parts of the engine directly. However, clients may configure me to use certain parts in the 3D rendering pipeline.Instance variables: vertexBuffer <B3DVertexBuffer> The vertex buffer passed on through the entire pipeline transformer <B3DEnginePart> The part performing transform operations shader <B3DEnginePart> The part performing vertex shading operations clipper <B3DEnginePart> The part performing view frustum clipping rasterizer <B3DEnginePart> The part performing final pixel rasterization!!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/14/1999 22:22'!clearDepthBuffer ^rasterizer clearDepthBuffer! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/16/1999 02:17'!clearViewport: aColor ^rasterizer clearViewport: aColor! !!B3DRenderEngine methodsFor: 'attributes'!color ^vertexBuffer color! !!B3DRenderEngine methodsFor: 'attributes'!color: aColor ^vertexBuffer color: aColor! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/7/1999 19:34'!material ^shader material! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/7/1999 19:34'!material: aMaterial ^shader material: aMaterial! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/7/1999 16:19'!materialColor ^shader materialColor! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/7/1999 16:19'!materialColor: aColor ^shader materialColor: aColor! !!B3DRenderEngine methodsFor: 'attributes'!normal ^vertexBuffer normal! !!B3DRenderEngine methodsFor: 'attributes'!normal: aVector ^vertexBuffer normal: aVector! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/7/1999 19:35'!popMaterial ^shader popMaterial.! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/16/1999 03:14'!popTexture ^rasterizer popTexture! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/7/1999 19:34'!pushMaterial ^shader pushMaterial.! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/16/1999 03:14'!pushTexture ^rasterizer pushTexture! !!B3DRenderEngine methodsFor: 'attributes'!texCoords ^vertexBuffer texCoords! !!B3DRenderEngine methodsFor: 'attributes'!texCoords: aVector ^vertexBuffer texCoords: aVector! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/16/1999 03:14'!texture ^rasterizer texture! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 6/2/1999 14:00'!texture: anObject "Note: For convenience; the object can be anything that understands #asTexture" ^rasterizer texture: anObject asTexture! !!B3DRenderEngine methodsFor: 'attributes'!vertex ^vertexBuffer vertex! !!B3DRenderEngine methodsFor: 'attributes'!vertex: aVector ^vertexBuffer vertex: aVector.! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/4/1999 17:52'!viewport ^rasterizer viewport! !!B3DRenderEngine methodsFor: 'attributes' stamp: 'ar 2/4/1999 17:52'!viewport: aRect ^rasterizer viewport: aRect! !!B3DRenderEngine methodsFor: 'draw primitives' stamp: 'ar 11/7/1999 18:12'!drawPolygonAfter: aBlock vertexBuffer reset. vertexBuffer primitive: 3. aBlock value. ^self renderPrimitive.! !!B3DRenderEngine methodsFor: 'draw primitives' stamp: 'ar 11/7/1999 18:15'!drawPolygonMesh: aB3DPolygonMesh "Draw a generic polygon mesh" | hasVtxNormals hasTexCoords hasVtxColors bounds box | box _ nil. aB3DPolygonMesh polygonsDo:[:poly| hasVtxNormals _ poly hasVertexNormals. hasTexCoords _ poly hasTextureCoords. hasVtxColors _ poly hasVertexColors. "Set the normal of the polygon if we don't have normals per vertex" hasVtxNormals ifFalse:[self normal: poly normal]. bounds _ self drawPolygonAfter:[ poly verticesDo:[:vtx| hasVtxColors ifTrue:[self color: (poly colorOfVertex: vtx)]. hasVtxNormals ifTrue:[self normal: (poly normalOfVertex: vtx)]. hasTexCoords ifTrue:[self texCoord: (poly texCoordOfVertex: vtx)]. self vertex: vtx. ]. ]. box == nil ifTrue:[box _ bounds] ifFalse:[box _ box quickMerge: bounds]. ]. ^box! !!B3DRenderEngine methodsFor: 'draw primitives' stamp: 'ar 2/4/1999 20:16'!render: anObject anObject renderOn: self.! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 2/8/1999 15:37'!privateClipVB: vb "Clip the objects in the vertex buffer." ^clipper processVertexBuffer: vb! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 2/2/1999 19:39'!privateNeedsClipVB: visibleFlag "Determine if a vertex buffer with the given visibility flag must be clipped. Return false if either visibleFlag == true (meaning the vertex buffer is completely inside the view frustum) or the rasterizer can clip by itself (it usually can)." ^visibleFlag ~~ true and:[rasterizer needsClip]! !!B3DRenderEngine methodsFor: 'private-rendering'!privateNeedsShadingVB "Return true if the objects in the vertex buffer needs separate shading. This is determined by checking if a) lighting is enabled b) at least one light exists c) at least one material exists " ^true! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 2/4/1999 04:26'!privateRasterizeVB: vb "Rasterize the current primitive from the vertex buffer." ^rasterizer processVertexBuffer: vb! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 2/4/1999 04:26'!privateShadeVB: vb "Shade all the vertices in the vertex buffer using selected materials and lights" ^shader processVertexBuffer: vb! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 2/8/1999 21:18'!privateTransformVB: vb "Transform the contents of the vertex buffer. Transforming may include normals (if lighting enabled) and textures (if textures enabled)." ^transformer processVertexBuffer: vb! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 2/2/1999 19:31'!privateVisibleVB: vb "Return the visibility of the objects in the vertex buffer. Return: true - if completely inside view frustum false - if completely outside view frustum nil - if partly inside/outside view frustum "! !!B3DRenderEngine methodsFor: 'private-rendering' stamp: 'ar 11/7/1999 18:11'!renderPrimitive "This is the main rendering loop for all operations" | visible | "Step 1: Check if the mesh is visible at all" visible _ self privateVisibleVB: vertexBuffer. visible == false ifTrue:[^nil]. "Step 2: Transform vertices, normals, texture coords of the mesh" self privateTransformVB: vertexBuffer. "Step 3: Light the vertices of the mesh." self privateNeedsShadingVB ifTrue:[self privateShadeVB: vertexBuffer]. "Step 4: Clip the mesh if necessary" (self privateNeedsClipVB: visible) ifTrue:[visible _ self privateClipVB: vertexBuffer]. visible == false ifTrue:[^nil]. "Step 5: Rasterize the mesh" ^self privateRasterizeVB: vertexBuffer.! !!B3DRenderEngine methodsFor: 'transforming' stamp: 'ar 2/4/1999 20:18'!loadIdentity ^transformer loadIdentity! !!B3DRenderEngine methodsFor: 'transforming'!lookFrom: position to: target up: upDirection ^transformer lookFrom: position to: target up: upDirection! !!B3DRenderEngine methodsFor: 'transforming'!perspective: aPerspective ^transformer perspective: aPerspective! !!B3DRenderEngine methodsFor: 'transforming' stamp: 'ar 2/5/1999 23:27'!popMatrix ^transformer popMatrix! !!B3DRenderEngine methodsFor: 'transforming' stamp: 'ar 2/5/1999 23:27'!pushMatrix ^transformer pushMatrix! !!B3DRenderEngine methodsFor: 'transforming'!rotateBy: aRotation ^transformer rotateBy: aRotation! !!B3DRenderEngine methodsFor: 'transforming' stamp: 'ar 2/15/1999 02:54'!scaleBy: value ^transformer scaleBy: value! !!B3DRenderEngine methodsFor: 'transforming'!transformBy: aTransformation ^transformer transformBy: aTransformation! !!B3DRenderEngine methodsFor: 'transforming' stamp: 'ar 2/4/1999 03:56'!translateBy: aVector ^transformer translateBy: aVector! !!B3DRenderEngine methodsFor: 'initialize' stamp: 'ar 2/16/1999 01:46'!destroy "Utility - destroy all resources associated with any part of the engine" transformer destroy. shader destroy. clipper destroy. rasterizer destroy.! !!B3DRenderEngine methodsFor: 'initialize' stamp: 'ar 2/16/1999 01:45'!finish "Flush the pipeline and force changes to the output medium" self flush. rasterizer finish.! !!B3DRenderEngine methodsFor: 'initialize' stamp: 'ar 2/5/1999 21:34'!flush "Flush the entire pipeline" transformer flush. shader flush. clipper flush. rasterizer flush.! !!B3DRenderEngine methodsFor: 'initialize' stamp: 'ar 4/18/1999 00:35'!initialize engine _ self. "Obviously ;-)" vertexBuffer _ B3DVertexBuffer new. transformer _ self class transformer engine: self. shader _ self class shader engine: self. clipper _ self class clipper engine: self. rasterizer _ self class rasterizer engine: self. self materialColor: Color white.! !!B3DRenderEngine methodsFor: 'initialize' stamp: 'ar 4/10/1999 22:51'!reset vertexBuffer reset. transformer reset. shader reset. clipper reset. rasterizer reset. self materialColor: Color white.! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/15/1999 20:24'!addLight: aLightSource "Add the given light source to the engine. Return a handle that can be used to modify the light source later on" ^shader addLight: (aLightSource transformedBy: transformer)! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/15/1999 20:25'!removeLight: lightHandle "Remove the light with the given handle from the engine." ^shader removeLight: lightHandle! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:30'!trackAmbientColor ^vertexBuffer trackAmbientColor! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:30'!trackAmbientColor: aBoolean ^vertexBuffer trackAmbientColor: aBoolean! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:31'!trackDiffuseColor ^vertexBuffer trackDiffuseColor! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:30'!trackDiffuseColor: aBoolean ^vertexBuffer trackDiffuseColor: aBoolean! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:31'!trackEmissionColor ^vertexBuffer trackEmissionColor! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:30'!trackEmissionColor: aBoolean ^vertexBuffer trackEmissionColor: aBoolean! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:31'!trackSpecularColor ^vertexBuffer trackSpecularColor! !!B3DRenderEngine methodsFor: 'shading' stamp: 'ar 2/8/1999 02:30'!trackSpecularColor: aBoolean ^vertexBuffer trackSpecularColor: aBoolean! !!B3DRenderEngine methodsFor: 'indexed primitives' stamp: 'ar 11/7/1999 18:12'!drawIndexedLines: indexArray vertices: vertexArray normals: normalArray colors: colorArray texCoords: texCoordArray vertexBuffer reset. vertexBuffer primitive: 4. vertexBuffer loadIndexed: indexArray vertices: vertexArray normals: normalArray colors: colorArray texCoords: texCoordArray. ^self renderPrimitive.! !!B3DRenderEngine methodsFor: 'indexed primitives' stamp: 'ar 11/7/1999 18:12'!drawIndexedQuads: indexArray vertices: vertexArray normals: normalArray colors: colorArray texCoords: texCoordArray vertexBuffer reset. vertexBuffer primitive: 6. vertexBuffer loadIndexed: indexArray vertices: vertexArray normals: normalArray colors: colorArray texCoords: texCoordArray. ^self renderPrimitive.! !!B3DRenderEngine methodsFor: 'indexed primitives' stamp: 'ar 11/7/1999 18:12'!drawIndexedTriangles: indexArray vertices: vertexArray normals: normalArray colors: colorArray texCoords: texCoordArray vertexBuffer reset. vertexBuffer primitive: 5. vertexBuffer loadIndexed: indexArray vertices: vertexArray normals: normalArray colors: colorArray texCoords: texCoordArray. ^self renderPrimitive.! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 5/26/2000 15:20'!clipRect "Return the current clipRect" ^rasterizer clipRect! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 5/26/2000 15:20'!clipRect: aRectangle "Set the current clipRect" ^rasterizer clipRect: aRectangle! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 4/17/1999 23:12'!getClipper "Private. Return the clipper used with this engine." ^clipper! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 4/17/1999 23:13'!getRasterizer "Private. Return the rasterizer used with this engine." ^rasterizer! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 4/17/1999 23:12'!getShader "Private. Return the shader used with this engine." ^shader! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 4/17/1999 23:12'!getTransformer "Private. Return the transformer used with this engine." ^transformer! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 4/17/1999 23:11'!getVertexBuffer "Private. Return the vertex buffer used with this engine." ^vertexBuffer! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 5/26/2000 15:19'!target "Return the rendering target" ^rasterizer target! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 5/26/2000 15:19'!target: aForm "Set the rendering target" ^rasterizer target: aForm! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 5/26/2000 15:18'!viewportOffset "Return the offset for the viewport" ^rasterizer viewportOffset! !!B3DRenderEngine methodsFor: 'private-access' stamp: 'ar 5/26/2000 15:16'!viewportOffset: aPoint "Set the offset for the viewport" ^rasterizer viewportOffset: aPoint! !!B3DRenderEngine methodsFor: 'picking' stamp: 'ar 4/18/1999 02:28'!asPickerAt: aPoint ^self asPickerAt: aPoint extent: 1@1! !!B3DRenderEngine methodsFor: 'picking' stamp: 'ar 4/17/1999 23:56'!asPickerAt: aPoint extent: extentPoint | picker | picker _ B3DPickerEngine new. picker loadFrom: self. picker pickAt: aPoint extent: extentPoint. ^picker! !!B3DRenderEngine methodsFor: 'picking' stamp: 'ar 2/27/2000 20:12'!pickingMatrixAt: aPoint extent: extentPoint "Return a matrix for picking at the given point using the given extent." ^self pickingMatrixFor: self viewport at: aPoint extent: extentPoint! !!B3DRenderEngine methodsFor: 'picking' stamp: 'ar 2/27/2000 20:10'!pickingMatrixFor: vp at: aPoint extent: extentPoint "Return a matrix for picking at the given point using the given extent." | m scaleX scaleY ofsX ofsY | scaleX _ vp width / extentPoint x. scaleY _ vp height / extentPoint y. ofsX _ (vp width + (2.0 * (vp origin x - aPoint x))) / extentPoint x. ofsY _ (vp height + (2.0 * (aPoint y - vp corner y))) / extentPoint y. m _ B3DMatrix4x4 identity. m a11: scaleX; a22: scaleY. m a14: ofsX; a24: ofsY. ^m! !!B3DRenderEngine methodsFor: 'properties' stamp: 'ar 11/7/1999 18:23'!hasProperty: propName "Answer whether the receiver has the given property. Deemed to have it only if I have a property dictionary entry for it and that entry is neither nil nor false" self valueOfProperty: propName ifAbsent:[^false]. ^true! !!B3DRenderEngine methodsFor: 'properties' stamp: 'ar 11/7/1999 18:25'!properties ^properties ifNil:[properties _ IdentityDictionary new].! !!B3DRenderEngine methodsFor: 'properties' stamp: 'ar 11/7/1999 18:23'!removeProperty: propName self valueOfProperty: propName ifAbsent:[^self]. self properties removeKey: propName.! !!B3DRenderEngine methodsFor: 'properties' stamp: 'ar 11/7/1999 18:22'!setProperty: propName toValue: aValue aValue ifNil: [^ self removeProperty: propName]. self properties at: propName put: aValue.! !!B3DRenderEngine methodsFor: 'properties' stamp: 'ar 11/7/1999 18:24'!valueOfProperty: propName ^self valueOfProperty: propName ifAbsent:[nil]! !!B3DRenderEngine methodsFor: 'properties' stamp: 'ar 11/7/1999 18:36'!valueOfProperty: propName ifAbsent: aBlock properties == nil ifTrue: [^ aBlock value]. ^properties at: propName ifAbsent: aBlock! !!B3DRenderEngine class methodsFor: 'instance creation' stamp: 'ar 5/26/2000 15:10'!defaultForPlatformOn: aForm "Return the render engine that is most appropriate for the current host platform." (B3DHardwareEngine isAvailableFor: aForm) ifTrue:[^B3DHardwareEngine newOn: aForm]. (B3DPrimitiveEngine isAvailableFor: aForm) ifTrue:[^B3DPrimitiveEngine newOn: aForm]. ^B3DRenderEngine newOn: aForm! !!B3DRenderEngine class methodsFor: 'instance creation'!new ^super new initialize! !!B3DRenderEngine class methodsFor: 'instance creation' stamp: 'ar 5/26/2000 15:49'!newOn: aForm ^(self new) target: aForm; yourself! !!B3DRenderEngine class methodsFor: 'accessing' stamp: 'ar 2/14/1999 01:37'!clipper "Return the transformer to use with this engine" ^B3DVertexClipper! !!B3DRenderEngine class methodsFor: 'accessing' stamp: 'ar 4/18/1999 05:27'!rasterizer "Return the rasterizer to use with this engine" ^B3DSimulRasterizer! !!B3DRenderEngine class methodsFor: 'accessing' stamp: 'ar 2/14/1999 01:37'!shader "Return the shader to use with this engine" ^B3DVertexShader! !!B3DRenderEngine class methodsFor: 'accessing' stamp: 'ar 2/14/1999 01:37'!transformer "Return the transformer to use with this engine" ^B3DVertexTransformer! !!B3DRenderEngine class methodsFor: 'testing' stamp: 'ar 2/14/1999 01:39'!isAvailable "Return true if this engine is available (e.g., all of its parts are avaiable)" ^(self transformer isAvailable and:[ self shader isAvailable and:[ self clipper isAvailable and:[ self rasterizer isAvailable]]])! !!B3DRenderEngine class methodsFor: 'testing' stamp: 'ar 2/16/1999 17:34'!isAvailableFor: anOutputMedium "Return true if this engine is available for the given output medium" ^(self transformer isAvailableFor: anOutputMedium) and:[ (self shader isAvailableFor: anOutputMedium) and:[ (self clipper isAvailableFor: anOutputMedium) and:[ (self rasterizer isAvailableFor: anOutputMedium)]]]! !I represent general 3d rotations by using Unit-Quaternions. Unit-Quaternions are one of the best available representation for rotations in computer graphics because they provide an easy way of doing arithmetic with them and also because they allow us to use spherical linear interpolation (so-called "slerps") of rotations.
-
- Indexed Variables:
- a <Float> the real part of the quaternion
- b <Float> the first imaginary part of the quaternion
- c <Float> the second imaginary part of the quaternion
- d <Float> the third imaginary part of the quaternion
-
- !!B3DRotation methodsFor: 'initialize' stamp: 'ar 2/1/1999 22:02'!a: aValue b: bValue c: cValue d: dValue self a: aValue. self b: bValue. self c: cValue. self d: dValue. (aValue < 0.0) ifTrue:[self *= -1.0]. self normalize.! !!B3DRotation methodsFor: 'initialize' stamp: 'ar 2/1/1999 22:02'!angle: anAngle axis: aVector3 self radiansAngle: anAngle degreesToRadians axis: aVector3! !!B3DRotation methodsFor: 'initialize' stamp: 'ar 2/1/1999 22:02'!from: startVector to: endVector "Create a rotation from startVector to endVector" | axis cos sin | axis := startVector cross: endVector. cos := (startVector dot: endVector) arcCos. sin := axis length. axis safelyNormalize. self a: cos b: axis x * sin c: axis y * sin d: axis z * sin. ! !!B3DRotation methodsFor: 'initialize' stamp: 'ar 2/1/1999 22:03'!radiansAngle: anAngle axis: aVector3 | angle sin cos | angle := anAngle / 2.0. cos := angle cos. sin := angle sin. self a: cos b: aVector3 x * sin c: aVector3 y * sin d: aVector3 z * sin.! !!B3DRotation methodsFor: 'initialize'!setIdentity ^self loadFrom: B3DIdentityRotation! !!B3DRotation methodsFor: 'initialize' stamp: 'ar 2/1/1999 22:03'!x: xValue y: yValue z: zValue a: anAngle | angle sin cos | angle := (anAngle degreesToRadians) / 2.0. cos := angle cos. sin := angle sin. self a: cos b: xValue * sin c: yValue * sin d: zValue * sin! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:59'!a ^self at: 1! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:59'!a: aFloat self at: 1 put: aFloat! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 22:04'!angle ^(self a arcCos * 2.0 radiansToDegrees)! !!B3DRotation methodsFor: 'accessing'!angle: newAngle self angle: newAngle axis: self axis! !!B3DRotation methodsFor: 'accessing'!axis | sinAngle | sinAngle := self a arcCos sin. sinAngle isZero ifTrue:[^B3DVector3 zero]. ^B3DVector3 x: (self b / sinAngle) y: (self c / sinAngle) z: (self d / sinAngle)! !!B3DRotation methodsFor: 'accessing'!axis: newAxis self angle: self angle axis: newAxis! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:59'!b ^self at: 2! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 22:00'!b: aFloat self at: 2 put: aFloat! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:59'!c ^self at: 3! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 22:00'!c: aFloat self at: 3 put: aFloat! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:59'!d ^self at: 4! !!B3DRotation methodsFor: 'accessing' stamp: 'ar 2/1/1999 22:00'!d: aFloat self at: 4 put: aFloat! !!B3DRotation methodsFor: 'arithmetic' stamp: 'ar 2/1/1999 22:05'!* aRotation "Multiplying two rotations is the same as concatenating the two rotations." | v1 v2 v3 vv | v1 := self bcd * aRotation a. v2 := aRotation bcd * self a. v3 := aRotation bcd cross: self bcd. vv := v1 + v2 + v3. ^B3DRotation a: (self a * aRotation a) - (self bcd dot: aRotation bcd) b: vv x c: vv y d: vv z! !!B3DRotation methodsFor: 'arithmetic' stamp: 'ar 2/1/1999 22:06'!negated "Negating a quaternion is the same as reversing the angle of rotation" ^B3DRotation a: self a negated b: self b c: self c d: self d! !!B3DRotation methodsFor: 'arithmetic' stamp: 'ar 9/17/1999 12:43'!normalize "Normalize the receiver. Note that the actual angle (a) determining the amount of rotation is fixed, since we do not want to modify angles. This leads to: a^2 + b^2 + c^2 + d^2 = 1. b^2 + c^2 + d^2 = 1 - a^2. Note also that the angle (a) can not exceed 1.0 (due its creation by cosine) and if it is 1.0 we have exactly the unit quaternion ( 1, [ 0, 0, 0]). " | oneMinusASquared length | oneMinusASquared := 1.0 - (self a squared). (oneMinusASquared < 1.0e-10) ifTrue:[^self setIdentity]. length := ((self b squared + self c squared + self d squared) / oneMinusASquared) sqrt. length = 0.0 ifTrue:[^self setIdentity]. self b: self b / length. self c: self c / length. self d: self d / length.! !!B3DRotation methodsFor: 'converting'!asMatrix4x4 "Given a quaternion q = (a, [ b, c , d]) the rotation matrix can be calculated as | 1 - 2(cc+dd), 2(bc-da), 2(db+ca) | m = | 2(bc+da), 1 - 2(bb+dd), 2(cd-ba) | | 2(db-ca), 2(cd+ba), 1 - 2(bb+cc) | " | a b c d m bb cc dd bc cd db ba ca da | a _ self a. b _ self b. c _ self c. d _ self d. bb := (b * b). cc := (c * c). dd := (d * d). bc := (b * c). cd := (c * d). db := (d * b). ba := (b * a). ca := (c * a). da := (d * a). m := self matrixClass identity. m a11: 1.0 - (cc + dd * 2.0);a12: (bc - da * 2.0); a13: (db + ca * 2.0); a21: (bc + da * 2.0); a22: 1.0 - (bb + dd * 2.0);a23: (cd - ba * 2.0); a31: (db - ca * 2.0); a32: (cd + ba * 2.0); a33: 1.0 - (bb + cc * 2.0). ^m! !!B3DRotation methodsFor: 'converting' stamp: 'ar 2/1/1999 22:08'!normalized ^self copy normalize! !!B3DRotation methodsFor: 'interpolating' stamp: 'jsp 2/25/1999 15:57'!interpolateTo: aRotation at: t "Spherical linear interpolation (slerp) from the receiver to aQuaternion" ^self slerpTo: aRotation at: t extraSpins: 0! !!B3DRotation methodsFor: 'interpolating' stamp: 'ar 2/1/1999 22:08'!slerpTo: aRotation at: t "Spherical linear interpolation (slerp) from the receiver to aQuaternion" ^self slerpTo: aRotation at: t extraSpins: 0! !!B3DRotation methodsFor: 'interpolating' stamp: 'ar 3/24/1999 14:58'!slerpTo: aRotation at: t extraSpins: spin "Sperical Linear Interpolation (slerp). Calculate the new quaternion when applying slerp from the receiver (t = 0.0) to aRotation (t = 1.0). spin indicates the number of extra rotations to be added. The code shown below is from Graphics Gems III" | cosT alpha beta flip theta phi sinT | alpha := t. flip := false. "calculate the cosine of the two quaternions on the 4d sphere" cosT := self dot: aRotation. "if aQuaternion is on the opposite hemisphere reverse the direction (note that in quaternion space two points describe the same rotation)" cosT < 0.0 ifTrue:[ flip := true. cosT := cosT negated]. "If the aQuaternion is nearly the same as I am use linear interpolation" cosT > 0.99999 ifTrue:[ "Linear Interpolation" beta := 1.0 - alpha ] ifFalse:[ "Spherical Interpolation" theta := cosT arcCos. phi := (spin * Float pi) + theta. sinT := theta sin. beta := (theta - (alpha * phi)) sin / sinT. alpha := (alpha * phi) sin / sinT]. flip ifTrue:[alpha := alpha negated]. ^B3DRotation a: (alpha * aRotation a) + (beta * self a) b: (alpha * aRotation b) + (beta * self b) c: (alpha * aRotation c) + (beta * self c) d: (alpha * aRotation d) + (beta * self d)! !!B3DRotation methodsFor: 'printing' stamp: 'ar 2/1/1999 22:09'!printOn: aStream aStream nextPutAll: self class name; nextPut:$(; print: self angle; nextPut: Character space; print: self axis; nextPut:$).! !!B3DRotation methodsFor: 'private'!bcd ^B3DVector3 x: self b y: self c z: self d! !!B3DRotation methodsFor: 'private' stamp: 'ar 2/1/1999 22:10'!matrixClass ^B3DMatrix4x4! !!B3DRotation class methodsFor: 'instance creation'!a: aValue b: bValue c: cValue d: dValue ^self new a: aValue b: bValue c: cValue d: dValue! !!B3DRotation class methodsFor: 'instance creation'!angle: anAngle axis: aVector3 ^self new angle: anAngle axis: aVector3! !!B3DRotation class methodsFor: 'instance creation'!axis: aVector3 angle: anAngle ^self angle: anAngle axis: aVector3! !!B3DRotation class methodsFor: 'instance creation'!from: startVector to: endVector ^self new from: startVector to: endVector! !!B3DRotation class methodsFor: 'instance creation'!identity ^self new setIdentity! !!B3DRotation class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:32'!numElements ^4! !!B3DRotation class methodsFor: 'instance creation'!radiansAngle: anAngle axis: aVector3 ^self new radiansAngle: anAngle axis: aVector3! !!B3DRotation class methodsFor: 'instance creation'!x: xValue y: yValue z: zValue a: anAngle ^self new x: xValue y: yValue z: zValue a: anAngle! !!B3DRotation class methodsFor: 'class initialization'!initialize "B3DRotation initialize" B3DIdentityRotation _ self new. B3DIdentityRotation floatAt: 1 put: 1.0.! !!B3DRotationArray class methodsFor: 'instance creation' stamp: 'ar 5/4/2000 15:45'!contentsClass ^B3DRotation! !I represent a mesh from Autodesk 3D Studio.!!B3DSTriangleMesh methodsFor: 'initialize' stamp: 'ar 2/7/1999 20:57'!from3DS: aDictionary | triList triSpec triSize tri flags | aDictionary isEmpty ifTrue:[^nil]. vertices _ aDictionary at: #vertexList. "matrix _ aDictionary at: #matrix ifAbsent:[nil]. matrix ifNotNil:[matrix quickTransformV3ArrayFrom: vertices to: vertices]." vtxTexCoords _ aDictionary at: #textureVertices ifAbsent:[nil]. triList _ aDictionary at: #triList. triSpec _ triList first. triSize _ triSpec size. faces _ B3DIndexedTriangleArray new: triSize. edgeFlags _ ByteArray new: triSize. 1 to: triSize do:[:i| tri _ (triSpec at: i) key. flags _ (triSpec at: i) value. faces at: i put: (B3DIndexedTriangle with: tri first with: tri second with: tri third). edgeFlags at: i put: flags]. triList second ifNotNil:[ smoothFlags _ WordArray new: triSize. triList second doWithIndex:[:smoothFlag :index| smoothFlags at: index put: smoothFlag]].! !!B3DSTriangleMesh methodsFor: 'private' stamp: 'ar 2/15/1999 06:44'!collectSplitVertices: aSet "Collect the non smooth vertices into a Dictionary vertex index -> Dictionary smoothing group -> list of face indexes. " | face flag vtxIndex groups groupDict | groupDict _ Dictionary new: aSet size * 2. 1 to: faces size do:[:faceIndex| face _ faces at: faceIndex. flag _ smoothFlags at: faceIndex. 1 to: 3 do:[:j| vtxIndex _ face at: j. (aSet includes: vtxIndex) ifTrue:[ groups _ groupDict at: vtxIndex ifAbsentPut:[Dictionary new]. (groups at: flag ifAbsentPut:[OrderedCollection new]) add: faceIndex. ]. ]. ]. ^groupDict! !!B3DSTriangleMesh methodsFor: 'private' stamp: 'ar 2/17/1999 15:59'!computeFunkyVertexNormals "Compute the vertex normals for the receiver. Don't split the faces so we'll get some funky lighting effects." vtxNormals _ super computeVertexNormals! !!B3DSTriangleMesh methodsFor: 'private' stamp: 'ar 2/17/1999 15:57'!computeVertexNormals "Compute the vertex normals for the receiver. Note: This is a multi pass process here - we may have to split up vertices" | set dict | set _ self detectNonSmoothVertices. set isEmpty ifFalse:[ "Collect the dictionary of vertices to split" dict _ self collectSplitVertices: set. "And actually split them" self splitVerticesFrom: dict. ]. "Now do the actual computation" ^super computeVertexNormals! !!B3DSTriangleMesh methodsFor: 'private' stamp: 'ar 2/15/1999 06:54'!detectNonSmoothVertices "Detect all the vertices in the receiver that cannot be easily smoothed" | mask face flag vtxIndex out newMask | smoothFlags ifNil:[^#()]. mask _ WordArray new: vertices size. mask atAllPut: 16rFFFFFFFF. out _ Set new: 1000. "Leave us enough space to avoid collisions" 1 to: faces size do:[:i| face _ faces at: i. flag _ smoothFlags at: i. 1 to: 3 do:[:j| vtxIndex _ face at: j. newMask _ ((mask at: vtxIndex) bitAnd: flag). newMask = 0 ifTrue:[out add: vtxIndex]. mask at: vtxIndex put: newMask. ]. ]. ^out! !!B3DSTriangleMesh methodsFor: 'private' stamp: 'ar 2/15/1999 06:49'!splitVerticesFrom: aDictionary "Split the non smooth vertices from the Dictionary vertex index -> Dictionary smoothing group -> list of face indexes. " | newVertices newColors newTexCoords nextIndex vtxIndex nValues skipAssoc faceList iFace | newVertices _ WriteStream with: vertices. vtxColors ifNotNil:[newColors _ WriteStream with: vtxColors]. vtxTexCoords ifNotNil:[newTexCoords _ WriteStream with: vtxTexCoords]. nextIndex _ vertices size. aDictionary associationsDo:[:vertexAssoc| vtxIndex _ vertexAssoc key. nValues _ vertexAssoc value size - 1. "We have to copy n values" newVertices next: nValues put: (vertices at: vtxIndex). newColors ifNotNil:[newColors next: nValues put: (vtxColors at: vtxIndex)]. newTexCoords ifNotNil:[newTexCoords next: nValues put: (vtxTexCoords at: vtxIndex)]. skipAssoc _ true. "Skip the first association - we can reuse the original vertex" vertexAssoc value associationsDo:[:smoothAssoc| skipAssoc ifFalse:[ faceList _ smoothAssoc value. nextIndex _ nextIndex + 1. faceList do:[:faceIndex| iFace _ faces at: faceIndex. 1 to: 3 do:[:i| (iFace at: i) = vtxIndex ifTrue:[iFace at: i put: nextIndex]]. faces at: faceIndex put: iFace. ]. ]. skipAssoc _ false. ]. ]. "Cleanup" vtxNormals _ nil. "Must be recomputed" vertices _ newVertices contents. newColors ifNotNil:[vtxColors _ newColors contents]. newTexCoords ifNotNil:[vtxTexCoords _ newTexCoords contents].! !!B3DSTriangleMesh class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 21:26'!from3DS: aDictionary ^self new from3DS: aDictionary! !!B3DScanner methodsFor: 'initialize' stamp: 'ar 4/18/1999 07:59'!initialize aet _ B3DActiveEdgeTable new. fillList _ B3DFillList new. added _ B3DPrimitiveEdgeList new. lastIntersection _ B3DPrimitiveEdge new. nextIntersection _ B3DPrimitiveEdge new. objects _ OrderedCollection new.! !!B3DScanner methodsFor: 'initialize' stamp: 'ar 4/18/1999 05:21'!setupObjects "Set up the list of objects (e.g., triangle inputs) by creating a linked list of objects which is sorted by the initial yValue of the tris." | lastObj | objects _ objects sortBy: [:obj1 :obj2| obj1 bounds origin sortsBefore: obj2 bounds origin]. lastObj _ nil. objects do:[:nextObj| nextObj reset. nextObj prevObj: lastObj. lastObj == nil ifFalse:[lastObj nextObj: nextObj]. lastObj _ nextObj. ]. lastObj == nil ifFalse:[lastObj nextObj: nil].! !!B3DScanner methodsFor: 'public' stamp: 'ar 4/18/1999 05:15'!addObject: primObj objects add: primObj.! !!B3DScanner methodsFor: 'public' stamp: 'ar 4/18/1999 05:29'!bitBlt: aBitBlt bitBlt _ aBitBlt.! !!B3DScanner methodsFor: 'public' stamp: 'ar 4/18/1999 07:55'!mainLoop | yValue nextObjY nextEdgeY obj activeStart passiveStart scaledY | objects size = 0 ifTrue:[^self]. "No input" self setupObjects. "Sort objects and create linked list" nFaces _ maxFaces _ maxEdges _ 0. "Pre-fetch first object to start from" activeStart _ passiveStart _ objects at: 1. yValue _ nextEdgeY _ nextObjY _ passiveStart bounds origin y. [activeStart == nil and:[passiveStart == nil and:[aet isEmpty]]] whileFalse:[ "Add new objects if necessary" yValue = nextObjY ifTrue:[ "Make sure we add edges from newly created objects" nextEdgeY _ nextObjY. "Add new objects" [passiveStart notNil and:[passiveStart bounds origin y = nextObjY]] whileTrue:[passiveStart _ passiveStart nextObj]. passiveStart == nil ifTrue:[nextObjY _ 99999]"Some large value" ifFalse:[nextObjY _ passiveStart bounds origin y]. ]. "End of adding new objects" "Add new edges if necessary" yValue = nextEdgeY ifTrue:[ nextEdgeY _ nextObjY bitShift: 12. "Some VERY large value" scaledY _ (yValue+1) bitShift: 12. obj _ activeStart. [obj == passiveStart] whileFalse:[ [obj atEnd not and:[obj peekY < scaledY]] whileTrue:[self addEdgesFromFace: obj next at: yValue]. obj atEnd ifTrue:[ obj == activeStart ifTrue:[activeStart _ obj nextObj] ifFalse:[obj prevObj nextObj: obj nextObj]. ] ifFalse:[obj peekY < nextEdgeY ifTrue:[nextEdgeY _ obj peekY]]. obj _ obj nextObj. ]. nextEdgeY _ (nextEdgeY bitShift: -12). ]. added isEmpty ifFalse:[ "Merge new edges into AET" "Note: These may be lower half edges." B3DScanner doDebug ifTrue:[self validateAETOrder]. aet mergeEdgesFrom: added. B3DScanner doDebug ifTrue:[ self validateAETOrder. self validateEdgesFrom: aet]. added reset. "Clean up the list" ]. "This is the core loop." "[yValue < nextEdgeY and:[added isEmpty and:[aet isEmpty not]]] whileTrue:[" B3DScanner doDebug ifTrue:[yValue printString displayAt: 0@0]. "gather stats" maxEdges _ maxEdges max: aet size. maxFaces _ maxFaces max: nFaces. "Scan out the AET" aet isEmpty ifFalse:[ self clearSpanBufferAt: yValue. self scanAETAt: yValue. self drawSpanBufferAt: yValue. "Advance to next y and update AET" ]. yValue _ yValue + 1. aet isEmpty ifFalse:[self updateAETAt: yValue]. "]." ]. nFaces = 0 ifFalse:[self error: nFaces printString,' remaining faces'].! !!B3DScanner methodsFor: 'public' stamp: 'ar 4/18/1999 05:31'!resetObjects objects _ OrderedCollection new.! !!B3DScanner methodsFor: 'public' stamp: 'ar 4/18/1999 05:28'!spanBuffer: aBitmap spanBuffer _ aBitmap.! !!B3DScanner methodsFor: 'aet adding' stamp: 'ar 4/18/1999 08:14'!addEdgesFromFace: face at: yValue "Add the two top edges from the given face to the aet. The top edges are (v0-v1) and (v0-v2) where (v0-v1) is the 'upper' half-edge of the triangle" | xValue index needMajor needMinor majorEdge minorEdge | face oneOverArea = 0.0 ifTrue:[^self]. needMinor _ needMajor _ true. "We need both edges" majorEdge _ minorEdge _ nil. xValue _ face vertex0 windowPosX. "Search the insertion list to merge the edges of the face" index _ added firstIndexForInserting: xValue. index _ added xValue: xValue from: index do:[:edge| (edge rightFace == nil and:[ "Note: edge vertex0 == face vertex0 should be the case for most meshes. But since it is advantegous for the scanner to have two faces per edge we're also checking for the actual vertex values." edge vertex0 == face vertex0 or:[ edge vertex0 rasterPos = face vertex0 rasterPos]]) ifTrue:[ "This edge is a possible candidate for adding the face" (needMajor and:["See above comment" edge vertex1 == face vertex2 or:[ edge vertex1 rasterPos = face vertex2 rasterPos]]) ifTrue:[ majorEdge _ edge. edge rightFace: face. edge flags: (edge flags bitOr: FlagEdgeRightMajor). nFaces _ nFaces + 1. needMinor ifFalse:[ ^self adjustFace: face major: majorEdge minor: minorEdge]. "Done." needMajor _ false. ] ifFalse:[ (needMinor and:["See above comment" edge vertex1 == face vertex1 or:[ edge vertex1 rasterPos = face vertex1 rasterPos]]) ifTrue:[ minorEdge _ edge. edge rightFace: face. edge flags: (edge flags bitOr: FlagContinueRightEdge). needMajor ifFalse:[ ^self adjustFace: face major: majorEdge minor: minorEdge]. "Done." needMinor _ false. ]. ]. ]. ]. "Need to add new edges. NOTE: index already points to the right point for insertion." needMajor ifTrue:[ majorEdge _ B3DPrimitiveEdge new. majorEdge v0: face vertex0 v1: face vertex2. majorEdge nLines = 0 ifTrue:[^self]. "Horizontal edge" majorEdge leftFace: face. majorEdge initializePass1. majorEdge flags: (majorEdge flags bitOr: FlagEdgeLeftMajor). nFaces _ nFaces + 1. ]. needMinor ifTrue:[ minorEdge _ B3DPrimitiveEdge new. minorEdge v0: face vertex0 v1: face vertex1. minorEdge leftFace: face. minorEdge flags: FlagContinueLeftEdge. "Note: If the (upper) minor edge is horizontal, use the lower one. Note: The lower minor edge cannot be horizontal if the major one isn't" minorEdge nLines = 0 ifTrue:[ needMajor ifTrue:[added add: majorEdge beforeIndex: index]. minorEdge _ self addLowerEdge: minorEdge fromFace: face. minorEdge nLines = 0 ifTrue:[self error:'Minor edge is horizontal']. ^self adjustFace: face major: majorEdge minor: minorEdge]. minorEdge flags: FlagContinueLeftEdge. minorEdge initializePass1. minorEdge xValue = xValue ifFalse:[self error:'Problem with minor edge']. minorEdge nLines = 0 ifTrue:[self error:'Minor edge is horizontal']. ]. needMajor & needMinor ifTrue:[ added add: majorEdge and: minorEdge beforeIndex: index. ] ifFalse:[ needMajor ifTrue:[added add: majorEdge beforeIndex: index] ifFalse:[added add: minorEdge beforeIndex: index]. ]. ^self adjustFace: face major: majorEdge minor: minorEdge.! !!B3DScanner methodsFor: 'aet adding' stamp: 'ar 4/18/1999 05:56'!addLowerEdge: oldEdge fromFace: face "Add the lower edge (v1-v2) from the given face. Return the newly created edge." | index minorEdge xValue | xValue _ face vertex1 windowPosX. index _ added firstIndexForInserting: xValue. index _ added xValue: xValue from: index do:[:edge| (edge rightFace == nil and:[ "See the comment in #addEdgesFromFace:at:" (edge vertex0 == face vertex1 and:[edge vertex1 == face vertex2]) or:[ edge vertex0 rasterPos = face vertex1 rasterPos and:[ edge vertex1 rasterPos = face vertex2 rasterPos]]]) ifTrue:[ "Adjust the left or right edge of the face" face leftEdge == oldEdge ifTrue:[face leftEdge: edge] ifFalse:[face rightEdge: edge]. edge rightFace: face. ^edge ]. ]. "Need to add new edge. NOTE: index already points to the right point for insertion." minorEdge _ B3DPrimitiveEdge new. minorEdge v0: face vertex1 v1: face vertex2. minorEdge nLines = 0 ifTrue:[^self]. "Horizontal" "Adjust left/right edge of the face" face leftEdge == oldEdge ifTrue:[face leftEdge: minorEdge] ifFalse:[face rightEdge: minorEdge]. minorEdge leftFace: face. minorEdge initializePass1. added add: minorEdge beforeIndex: index. ^minorEdge! !!B3DScanner methodsFor: 'aet adding' stamp: 'ar 4/8/1999 03:02'!adjustFace: face major: majorEdge minor: minorEdge "Set the left/right edge of the face to the appropriate edges" (majorEdge == nil or:[minorEdge == nil]) ifTrue:[^self error:'Edges must be non-nil']. majorEdge xValue = minorEdge xValue ifTrue:[ "Most likely case. Both edges start at the same point. Use dx/dy slope for determining which one is left and which one is right. NOTE: We have this already computed during face>>initializePass1. The value to use is the x increment at each scan line. NOTE2: There is also a border case when minorEdge is actually the lower edge of the triangle. If both xValues are equal, then the triangle is degenerate (e.g., it's area is zero) in which case the meaning of 'left' or 'right' does not matter at all (and can thus be handled by this simple test)." majorEdge xIncrement <= minorEdge xIncrement ifTrue:[ face leftEdge: majorEdge. face rightEdge: minorEdge] ifFalse:[ face leftEdge: minorEdge. face rightEdge: majorEdge]. ] ifFalse:[ "If the x values are not equal, simply use the edge with the smaller x value as 'left' edge" majorEdge xValue < minorEdge xValue ifTrue:[ face leftEdge: majorEdge. face rightEdge: minorEdge] ifFalse:[ face leftEdge: minorEdge. face rightEdge: majorEdge]. ].! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/18/1999 05:57'!adjustIntersectionsAt: yValue from: topEdge "The top face has changed. Adjust for possible intersections in the same scan line." | frontFace backFace | frontFace _ fillList first. "If frontFace is nil then the fillList is empty. If frontFace nextFace is nil then there is only one face in the list." (frontFace == nil or:[frontFace nextFace == nil]) ifTrue:[^self]. "Now, search the fill list until we reach the first face with minZ > face maxZ. Note that we have a linked list and can thus start from frontFace nextFace until we reach the end of the face list (nil)." backFace _ frontFace nextFace. [backFace == nil] whileFalse:[ (self checkIntersectionOf: frontFace with: backFace at: yValue edge: topEdge) ifFalse:[^self]. "Aborted." backFace _ backFace nextFace. ].! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/13/1999 01:00'!checkIntersectionOf: frontFace with: backFace at: yValue edge: leftEdge "Compute the possible intersection of frontFace and backFace at the given y value. Store the earliest intersection in nextIntersection. Return false if the face enumeration should be aborted, true otherwise. leftEdge is the edge defining the left-most boundary for possible intersections (e.g., all intersections have to be >= leftEdge xValue)" | floatX floatY frontZ backZ xValue rightX | backFace minZ >= frontFace maxZ ifTrue:[^false]. "Abort. Everything behind will be further away." "Check for shared edge of faces" frontFace leftEdge == backFace leftEdge ifTrue:[^true]. "Proceed." frontFace rightEdge == backFace rightEdge ifTrue:[^true]. "Proceed." "Check for newly created front face" (frontFace leftEdge xValue bitShift: -12) = (frontFace rightEdge xValue bitShift: -12) ifTrue:[^false]. "Abort" "Check for newly created back face" (backFace leftEdge xValue bitShift: -12) = (backFace rightEdge xValue bitShift: -12) ifTrue:[^true]. "Proceed" "Compute the z value of either frontFace or backFace depending on whose right edge x value is less (so we test a point that is inside both faces)" floatY _ yValue. frontFace rightEdge xValue <= backFace rightEdge xValue ifTrue:[ "Use frontFace rightEdge as reference value" frontZ _ frontFace rightEdge zValue. rightX _ frontFace rightEdge xValue. floatX _ rightX / 4096.0. backZ _ backFace zValueAtX: floatX y: floatY. ] ifFalse:[ "Use backFace rightEdge as reference value" backZ _ backFace rightEdge zValue. rightX _ backFace rightEdge xValue. floatX _ rightX / 4096.0. frontZ _ frontFace zValueAtX: floatX y: floatY. ]. backZ < frontZ ifTrue:[ "Found a possible intersection." xValue _ self computeIntersectionOf: frontFace with: backFace at: yValue ifError: leftEdge xValue. "The following tests for numerical inaccuracies" xValue > rightX ifTrue:[xValue _ rightX]. xValue < leftEdge xValue ifTrue:[ "In theory, this cannot happen. We may, however, have slight numerical inaccuracies here, too. Conceptually, we treat these intersections as if they occured immediately at the same fractional pixel in the scan line." xValue _ leftEdge xValue]. (xValue bitShift: -12) = (leftEdge xValue bitShift: -12) ifTrue:[ "Intersections at the same pixel are ignored. Process it at the next pixel. NOTE: This step is incredibly important!! It is by ignoring intersections at the same pixel that we can never run in an endless repetition of intersections at the same pixel value." xValue _ (leftEdge xValue bitShift: -12) + 1 bitShift: 12. ]. xValue < nextIntersection xValue ifTrue:[ nextIntersection xValue: xValue. nextIntersection leftFace: frontFace. nextIntersection rightFace: backFace. ]. ]. ^true "proceed"! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/8/1999 03:14'!computeIntersectionOf: frontFace with: backFace at: yValue ifError: errorValue "Compute the z intersection at the given y value" | dx1 dz1 dx2 dz2 px pz det det2 | dx1 _ frontFace rightEdge xValue - frontFace leftEdge xValue. dz1 _ frontFace rightEdge zValue - frontFace leftEdge zValue. dx2 _ backFace rightEdge xValue - backFace leftEdge xValue. dz2 _ backFace rightEdge zValue - backFace leftEdge zValue. px _ backFace leftEdge xValue - frontFace leftEdge xValue. pz _ backFace leftEdge zValue - frontFace leftEdge zValue. "Solve the linear equation using cramers rule" det _ (dx1 * dz2) - (dx2 * dz1). det = 0.0 ifTrue:[^errorValue]. "det1 _ (dx1 * pz) - (px * dz1)." det2 _ (px * dz2) - (pz * dx2). "det1 _ det1 / det." det2 _ det2 / det. ^frontFace leftEdge xValue + (dx1 * det2) truncated! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/8/1999 03:15'!isOnTop: edge at: yValue "Return true if the edge is on top of the current front face" | topFace floatX floatY | topFace _ fillList first. topFace == nil ifTrue:[^true]. "Note: It is important to return true if the edge is shared by the top face" (edge leftFace == topFace or:[edge rightFace == topFace]) ifTrue:[^true]. floatX _ edge xValue / 4096.0. floatY _ yValue. ^edge zValue < (fillList first zValueAtX: floatX y: floatY).! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/18/1999 07:23'!scanAETAt: yValue "Scan out and draw the active edge table" | leftEdge rightEdge tmp | aet reset. aet atEnd ifTrue:[^nil]. "Note the following is debug code that allows restarting this method without getting confused by the face flags. In release mode, having faces in the fillList here would be either an error or due to clipping at the right boundary." fillList do:[:face| face flags: (face flags bitXor: FlagFaceActive)]. fillList reset. nextIntersection xValue: 16r3FFFFFFF. "Out of reach" leftEdge _ aet next. "No do the AET scan" [aet atEnd] whileFalse:[ "The left edge here is always a top edge. Toggle its fills." self toggleTopFillsOf: leftEdge at: yValue. "After we got a new top face we have to adjust possible intersections." self adjustIntersectionsAt: yValue from: leftEdge. "Search for the next top edge, which will be the right boundary." rightEdge _ self searchForNewTopEdgeFrom: leftEdge at: yValue. "And fill the stuff" self fillFrom: leftEdge to: rightEdge at: yValue. leftEdge _ rightEdge. "Use a new intersection edge if necessary" leftEdge == nextIntersection ifTrue:[ tmp _ nextIntersection. nextIntersection _ lastIntersection. lastIntersection _ tmp]. nextIntersection xValue: 16r3FFFFFFF "Must be waaaay off to the right ;-)" ]. self toggleBackFillsOf: leftEdge at: yValue validate: false. fillList isEmpty ifFalse:[self error:'FillList not empty'].! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/18/1999 05:59'!searchForNewTopEdgeFrom: leftEdge at: yValue "Find the next top edge in the AET. Note: We have to make sure that intersection edges are returned appropriately." | edge topFace | topFace _ fillList first. topFace == nil ifTrue:[^aet next]. "Next edge must be top" [aet atEnd] whileFalse:[ "Check if we have an intersection first." nextIntersection xValue <= aet peek xValue ifTrue:[^nextIntersection]. edge _ aet next. "Check if the edge is on top" (self isOnTop: edge at: yValue) ifTrue:[^edge]. "If the edge is not on top, toggle the (back) fills of it" self toggleBackFillsOf: edge at: yValue validate: true. ]. ^nil! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/7/1999 04:40'!toggleBackFillsOf: edge at: yValue validate: aBool "Toggle the faces of the (back) edge" | face | face _ edge leftFace. (face flags anyMask: FlagFaceActive) ifTrue:[ (aBool and:[face == fillList first]) ifTrue:[self error:'Not a back face']. fillList remove: face] ifFalse:[ fillList addBack: face. "Check for possible intersections of back and front face" self checkIntersectionOf: fillList first with: face at: yValue edge: edge]. face flags: (face flags bitXor: FlagFaceActive). face _ edge rightFace. face == nil ifTrue:[^self]. (face flags anyMask: FlagFaceActive) ifTrue:[ (aBool and:[face == fillList first]) ifTrue:[self error:'Not a back face']. fillList remove: face] ifFalse:[ fillList addBack: face. "Check for possible intersections of back and front face" self checkIntersectionOf: fillList first with: face at: yValue edge: edge]. face flags: (face flags bitXor: FlagFaceActive).! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/5/1999 23:44'!toggleIntersectionEdge: edge "Toggle the faces of the given intersection edge. This is a *very* special case." fillList first == edge leftFace ifFalse:[^self error:'Left face of intersection edge not top face']. fillList remove: edge rightFace. fillList addFront: edge rightFace. ! !!B3DScanner methodsFor: 'aet scanning' stamp: 'ar 4/18/1999 06:01'!toggleTopFillsOf: edge at: yValue "Toggle the faces of the (new top) edge. We must carefully treat each of the following cases: 1) rightFace notNil (e.g., two faces) a) rightFace active ~= leftFace active => simply swap leftFace and rightFace in the face list b) rightFace active not & leftFace active not => edge defines new boundary entry; check for minimal dxdz and insert in order c) rightFace active & leftFace active => edge defines boundary exit; search all faces for minimal z value 2) rightFace isNil (e.g., single face) a) leftFace active => edge defines boundary exit; see 1c) b) leftFace active not => edge defines boundary entry; simply put it on top. " | leftFace rightFace xorMask noTest | edge == lastIntersection ifTrue:[^self toggleIntersectionEdge: edge]. noTest _ true. leftFace _ edge leftFace. rightFace _ edge rightFace. rightFace == nil ifTrue:[ (leftFace flags anyMask: FlagFaceActive) ifTrue:[ leftFace == fillList first | noTest ifFalse:[self error:'Oops']. fillList remove: leftFace. fillList searchForNewTopAtX: edge xValue y: yValue] ifFalse:[ fillList addFront: leftFace]. leftFace flags: (leftFace flags bitXor: FlagFaceActive). ^self]. "rightFace notNil" xorMask _ leftFace flags bitXor: rightFace flags. (xorMask anyMask: FlagFaceActive) ifTrue:[ "Simply swap" (leftFace flags anyMask: FlagFaceActive) ifTrue:[ leftFace == fillList first | noTest ifFalse:[self error:'Oops']. fillList remove: leftFace. fillList addFront: rightFace] ifFalse:[ rightFace == fillList first | noTest ifFalse:[self error:'Oops']. fillList remove: rightFace. fillList addFront: leftFace]. ] ifFalse:["rightFace active = leftFace active" (leftFace flags anyMask: FlagFaceActive) ifTrue:[ (leftFace == fillList or:[rightFace == fillList first]) | noTest ifFalse:[self error:'Oops']. fillList remove: leftFace. fillList remove: rightFace. fillList searchForNewTopAtX: edge xValue y: yValue. ] ifFalse:[ leftFace dzdx <= rightFace dzdx ifTrue:[ fillList addFront: leftFace. fillList addBack: rightFace] ifFalse:[ fillList addFront: rightFace. fillList addBack: leftFace]. ]. ]. leftFace flags: (leftFace flags bitXor: FlagFaceActive). rightFace flags: (rightFace flags bitXor: FlagFaceActive).! !!B3DScanner methodsFor: 'aet updating' stamp: 'ar 4/18/1999 06:02'!updateAETAt: yValue "Advance all entries in the AET by one scan line step" | edge count | aet reset. [aet atEnd] whileFalse:[ edge _ aet next. count _ edge nLines - 1. count = 0 ifTrue:[ "Remove the edge from the AET. If the continuation flag is set, create new (lower) edge(s)." (edge vertex1 windowPosY bitShift: -12) = yValue ifFalse:[self error:'Edge exceeds range']. aet removeFirst. (edge flags anyMask: FlagContinueLeftEdge) ifTrue:[self addLowerEdge: edge fromFace: edge leftFace]. (edge flags anyMask: FlagContinueRightEdge) ifTrue:[self addLowerEdge: edge fromFace: edge rightFace]. (edge flags anyMask: FlagEdgeLeftMajor) ifTrue:[nFaces _ nFaces - 1]. (edge flags anyMask: FlagEdgeRightMajor) ifTrue:[nFaces _ nFaces - 1]. ] ifFalse:[ "Edge continues. Adjust the number of scan lines remaining and update the incremental values. Make sure that the sorting order of the AET is not getting confused." edge nLines: count. "# of scan lines" edge stepToNextLine. "update incremental values" aet resortFirst. "make sure edge is sorted right" ]. ].! !!B3DScanner methodsFor: 'span drawing' stamp: 'ar 4/18/1999 05:45'!clearSpanBufferAt: yValue spanBuffer primFill: 0.! !!B3DScanner methodsFor: 'span drawing' stamp: 'ar 4/18/1999 06:46'!drawSpanBufferAt: yValue | leftX rightX | leftX _ aet first xValue bitShift: -12. rightX _ aet last xValue bitShift: -12. bitBlt copyBitsFrom: leftX to: rightX at: yValue.! !!B3DScanner methodsFor: 'span drawing' stamp: 'ar 4/18/1999 06:55'!fillFrom: leftEdge to: rightEdge at: yValue | face | leftEdge xValue >= rightEdge xValue ifTrue:[^self]. "Nothing to do" face _ fillList first. face == nil ifTrue:[^self]. face texture == nil ifTrue:[self rgbFill: face from: leftEdge to: rightEdge at: yValue] ifFalse:[self rgbstwFill: face from: leftEdge to: rightEdge at: yValue]! !!B3DScanner methodsFor: 'span drawing' stamp: 'ar 4/18/1999 06:48'!rgbFill: face from: leftEdge to: rightEdge at: yValue "Using only RGB (no alpha no textures)" | leftX rightX floatY floatX rValue gValue bValue pv rAttr gAttr bAttr | "Note: We always sample at pixel centers. If the edges do not include this pixel center, do nothing. Otherwise fill from leftX to rightX, including both pixels." leftX _ (leftEdge xValue bitShift: -12) + 1. rightX _ rightEdge xValue bitShift: -12. leftX < 0 ifTrue:[leftX _ 0]. rightX >= spanBuffer size ifTrue:[rightX _ spanBuffer size-1]. leftX > rightX ifTrue:[^self]. B3DScanner doDebug ifTrue:[ "Sanity check." (face leftEdge xValue > leftEdge xValue) ifTrue:[ (face rightEdge xValue < rightEdge xValue) ifTrue:[self error:'Filling outside face'] ifFalse:[self error:'Filling left of face']. ] ifFalse:[(face rightEdge xValue < rightEdge xValue) ifTrue:[self error:'Filling right of face']]. ]. (face flags anyMask: FlagFaceInitialized) ifFalse:[ face initializePass2. face flags: (face flags bitOr: FlagFaceInitialized)]. "@@: Sampling problem!!" floatY _ yValue + 0.5. floatX _ leftX. rAttr _ face attributes. gAttr _ rAttr nextAttr. bAttr _ gAttr nextAttr. rValue _ (face attrValue: rAttr atX: floatX y: floatY). gValue _ (face attrValue: gAttr atX: floatX y: floatY). bValue _ (face attrValue: bAttr atX: floatX y: floatY). [leftX <= rightX] whileTrue:[ rValue _ rValue min: 255.0 max: 0.0. gValue _ gValue min: 255.0 max: 0.0. bValue _ bValue min: 255.0 max: 0.0. pv _ (bValue truncated) + (gValue truncated bitShift: 8) + (rValue truncated bitShift: 16). spanBuffer at: (leftX _ leftX+1) put: (pv bitOr: 4278190080). rValue _ rValue + rAttr dvdx. gValue _ gValue + gAttr dvdx. bValue _ bValue + bAttr dvdx].! !!B3DScanner methodsFor: 'span drawing' stamp: 'ar 4/18/1999 07:22'!rgbstwFill: face from: leftEdge to: rightEdge at: yValue "Using only RGB & STW (no alpha)" | leftX rightX floatY floatX rValue gValue bValue pv rAttr gAttr bAttr aAttr wAttr sAttr tAttr wValue sValue tValue texColor | "Note: We always sample at pixel centers. If the edges do not include this pixel center, do nothing. Otherwise fill from leftX to rightX, including both pixels." leftX _ (leftEdge xValue bitShift: -12) + 1. rightX _ rightEdge xValue bitShift: -12. leftX < 0 ifTrue:[leftX _ 0]. rightX >= spanBuffer size ifTrue:[rightX _ spanBuffer size-1]. leftX > rightX ifTrue:[^self]. B3DScanner doDebug ifTrue:[ "Sanity check." (face leftEdge xValue > leftEdge xValue) ifTrue:[ (face rightEdge xValue < rightEdge xValue) ifTrue:[self error:'Filling outside face'] ifFalse:[self error:'Filling left of face']. ] ifFalse:[(face rightEdge xValue < rightEdge xValue) ifTrue:[self error:'Filling right of face']]. ]. (face flags anyMask: FlagFaceInitialized) ifFalse:[ face initializePass2. face flags: (face flags bitOr: FlagFaceInitialized)]. "@@: Sampling problem!!" floatY _ yValue + 0.5. floatX _ leftX. rAttr _ face attributes. gAttr _ rAttr nextAttr. bAttr _ gAttr nextAttr. aAttr _ bAttr nextAttr. wAttr _ aAttr nextAttr. sAttr _ wAttr nextAttr. tAttr _ sAttr nextAttr. rValue _ (face attrValue: rAttr atX: floatX y: floatY). gValue _ (face attrValue: gAttr atX: floatX y: floatY). bValue _ (face attrValue: bAttr atX: floatX y: floatY). wValue _ (face attrValue: wAttr atX: floatX y: floatY). sValue _ (face attrValue: sAttr atX: floatX y: floatY). tValue _ (face attrValue: tAttr atX: floatX y: floatY). [leftX <= rightX] whileTrue:[ rValue _ rValue min: 255.0 max: 0.0. gValue _ gValue min: 255.0 max: 0.0. bValue _ bValue min: 255.0 max: 0.0. texColor _ self textureColor: face texture atS: (sValue / wValue) atT: (tValue / wValue). pv _ (bValue * texColor blue) truncated + ((gValue * texColor green) truncated bitShift: 8) + ((rValue * texColor red) truncated bitShift: 16). spanBuffer at: (leftX _ leftX+1) put: (pv bitOr: 4278190080). rValue _ rValue + rAttr dvdx. gValue _ gValue + gAttr dvdx. bValue _ bValue + bAttr dvdx. wValue _ wValue + wAttr dvdx. sValue _ sValue + sAttr dvdx. tValue _ tValue + tAttr dvdx].! !!B3DScanner methodsFor: 'span drawing' stamp: 'ar 5/28/2000 12:19'!textureColor: aTexture atS: sValue atT: tValue "Return the interpolated color of the given texture at s/t" | w h fragS fragT sIndex tIndex peeker tex00 tex01 tex10 tex11 sFrac tFrac mixed | w _ aTexture width. h _ aTexture height. fragS _ w * sValue. fragT _ h * tValue. sIndex _ fragS truncated. tIndex _ fragT truncated. peeker _ BitBlt current bitPeekerFromForm: aTexture. tex00 _ (peeker pixelAt: (sIndex \\ w)@(tIndex \\ h)) asColorOfDepth: aTexture depth. tex01 _ (peeker pixelAt: (sIndex+1 \\ w)@(tIndex \\ h)) asColorOfDepth: aTexture depth. tex10 _ (peeker pixelAt: (sIndex \\ w)@(tIndex+1 \\ h)) asColorOfDepth: aTexture depth. tex11 _ (peeker pixelAt: (sIndex+1 \\ w)@(tIndex+1 \\ h)) asColorOfDepth: aTexture depth. sFrac _ fragS \\ 1.0. tFrac _ fragT \\ 1.0. mixed _ ((1.0 - tFrac) * (((1.0 - sFrac) * tex00 asB3DColor) + (sFrac * tex01 asB3DColor))) + (tFrac * (((1.0 - sFrac) * tex10 asB3DColor) + (sFrac * tex11 asB3DColor))). ^mixed! !!B3DScanner methodsFor: 'misc' stamp: 'ar 4/6/1999 03:49'!validateAETOrder | last next | aet isEmpty ifTrue:[^self]. aet reset. last _ aet next. [aet atEnd] whileFalse:[ next _ aet next. last xValue <= next xValue ifFalse:[^self error:'AET is broken']. last _ next].! !!B3DScanner methodsFor: 'misc' stamp: 'ar 4/7/1999 05:20'!validateEdgesFrom: aCollection "aCollection must contain two entries for each face." | faceNum face faces | faceNum _ 0. aCollection do:[:edge| edge leftFace ifNil:[self error:'Bad edge'] ifNotNil:[faceNum _ faceNum + 1]. edge rightFace ifNotNil:[faceNum _ faceNum + 1]. ]. faceNum \\ 2 = 0 ifTrue:[^self]. faces _ Bag new. aCollection do:[:edge| face _ edge leftFace. faces add: face. (aet indexOf: face leftEdge) = 0 ifTrue:[self error:'Left edge not in AET']. (aet indexOf: face rightEdge) = 0 ifTrue:[self error:'Right edge not in AET']. face _ edge rightFace. face == nil ifFalse:[ faces add: face. (aet indexOf: face leftEdge) = 0 ifTrue:[self error:'Left edge not in AET']. (aet indexOf: face rightEdge) = 0 ifTrue:[self error:'Right edge not in AET']. ]. ]. self error:'Something *IS* wrong here'.! !!B3DScanner class methodsFor: 'class initialization' stamp: 'ar 4/8/1999 18:30'!initialize "B3DScanner initialize" FlagContinueLeftEdge _ 1. FlagContinueRightEdge _ 2. FlagEdgeLeftMajor _ 4. FlagEdgeRightMajor _ 8. FlagFaceActive _ 1. FlagFaceInitialized _ 2.! !!B3DScanner class methodsFor: 'instance creation' stamp: 'ar 4/4/1999 04:27'!new ^super new initialize! !!B3DScanner class methodsFor: 'accessing' stamp: 'ar 4/18/1999 07:24'!doDebug ^DebugMode == true! !!B3DScanner class methodsFor: 'accessing' stamp: 'ar 4/18/1999 07:25'!doDebug: aBool "B3DScanner doDebug: true" "B3DScanner doDebug: false" DebugMode _ aBool.! !!B3DScene methodsFor: 'initialize' stamp: 'ti 3/28/2000 13:14'!from3DS: aDictionary "Remove the globals from the scene - the remaining objects are name->sceneObject " | globals constants ambient texture funkyNormals r1 | globals _ aDictionary at: #globals. constants _ globals at: #constants ifAbsent: [Dictionary new]. aDictionary removeKey: #globals. "Collect the scene objects and assign the names" objects _ OrderedCollection new. aDictionary associationsDo: [:assoc | objects add: ((B3DSceneObjectfrom3DS: assoc value) name: assoc key)]. "Fetch the cameras and set a default camera" cameras _ globals at: #cameras. cameras isEmpty ifTrue: [defaultCamera _ B3DCamera new position: 0 @ 0 @ 0] ifFalse: [defaultCamera _ cameras at: cameras keysasSortedCollection first]. "Fetch the lights" lights _ globals at: #lights. "Add the ambient light if possible. Note: The name $AMBIENT$ is used in the keyframe section of the 3DS file. " ambient _ constants at: 'ambientColor' ifAbsent: [B3DColor4 r: 0.0 g: 0.0 b: 0.0 a: 0.0]. ambient ifNotNil: [lights at: '$AMBIENT$' put: (B3DAmbientLightcolor: ambient)]. "Fetch the background color" clearColor _ constants at: 'backgroundColor' ifAbsent: [Color white]. "Fetch the materials and replace names in sceneObjects by actual materials " materials _ globals at: #materials. "Compute the per vertex normals" funkyNormals _ self confirm: 'Do you want funky normals instead ofaccurate normals?(It will give the model a somewhat strange, but interesting look)'. 'Computing vertex normals' displayProgressAt: Sensor cursorPoint from: 0 to: objects size during: [:bar | objects doWithIndex: [:obj :index | bar value: index. obj material ifNotNil: [objmaterial: (materials at: obj material ifAbsent: [])]. funkyNormals ifTrue: [obj geometrycomputeFunkyVertexNormals] ifFalse: [obj geometryvertexNormals]]]. (self confirm: 'Do you want to use a texture with the model?') ifTrue: [Utilities informUser: 'Choose a rectangle withinteresting stuff' during: [r1 _ Rectangle originFromUser: 128@ 128. Sensor waitNoButton]. texture _ B3DTexture fromDisplay: r1. texture wrap: true. texture interpolate: false. texture envMode: 0]. objects do: [:obj | obj texture ifNotNil: [obj texture: texture]]! !!B3DScene methodsFor: 'initialize' stamp: 'ar 2/17/1999 05:09'!initialize objects _ OrderedCollection new. cameras _ OrderedCollection new. lights _ OrderedCollection new. materials _OrderedCollection new.! !!B3DScene methodsFor: 'initialize' stamp: 'ti 3/28/2000 13:11'!withoutQuestionsFrom3DS: aDictionary "Remove the globals from the scene - the remaining objects are name->sceneObject " | globals constants ambient texture funkyNormals | globals _ aDictionary at: #globals. constants _ globals at: #constants ifAbsent: [Dictionary new]. aDictionary removeKey: #globals. "Collect the scene objects and assign the names" objects _ OrderedCollection new. aDictionary associationsDo: [:assoc | objects add: ((B3DSceneObjectfrom3DS: assoc value) name: assoc key)]. "Fetch the cameras and set a default camera" cameras _ globals at: #cameras. cameras isEmpty ifTrue: [defaultCamera _ B3DCamera new position: 0 @ 0 @ 0] ifFalse: [defaultCamera _ cameras at: cameras keysasSortedCollection first]. "Fetch the lights" lights _ globals at: #lights. "Add the ambient light if possible. Note: The name $AMBIENT$ is used in the keyframe section of the 3DS file. " ambient _ constants at: 'ambientColor' ifAbsent: [B3DColor4 r: 0.0 g: 0.0 b: 0.0 a: 0.0]. ambient ifNotNil: [lights at: '$AMBIENT$' put: (B3DAmbientLightcolor: ambient)]. "Fetch the background color" clearColor _ constants at: 'backgroundColor' ifAbsent: [Color white]. "Fetch the materials and replace names in sceneObjects by actual materials " materials _ globals at: #materials. "Compute the per vertex normals" funkyNormals _ false. 'Computing vertex normals' displayProgressAt: Sensor cursorPoint from: 0 to: objects size during: [:bar | objects doWithIndex: [:obj :index | bar value: index. obj material ifNotNil: [objmaterial: (materials at: obj material ifAbsent: [])]. funkyNormals ifTrue: [obj geometrycomputeFunkyVertexNormals] ifFalse: [obj geometryvertexNormals]]]. objects do: [:obj | obj texture ifNotNil: [obj texture: texture]]! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/15/1999 01:01'!boundingBox |bBox| box ifNotNil:[^box]. bBox _ nil. objects do:[:obj| bBox _ bBox ifNil:[obj boundingBox] ifNotNil:[bBox merge: obj boundingBox] ]. ^box _ bBox! !!B3DScene methodsFor: 'accessing' stamp: 'ti 3/21/2000 11:57'!cameras ^cameras! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:44'!clearColor ^clearColor! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:44'!clearColor: aColor clearColor _ aColor! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/15/1999 05:29'!defaultCamera ^defaultCamera! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/17/1999 05:08'!defaultCamera: aCamera defaultCamera _ aCamera.! !!B3DScene methodsFor: 'accessing' stamp: 'jsp 3/1/1999 10:46'!lights ^lights! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/17/1999 05:14'!objects ^objects! !!B3DScene methodsFor: 'accessing' stamp: 'ar 2/17/1999 05:14'!objects: aCollection objects _ aCollection! !!B3DScene methodsFor: 'displaying' stamp: 'ar 5/28/2000 12:24'!render | b3d | b3d _ (B3DRenderEngine defaultForPlatformOn: Display). b3d viewport: (0@0 extent: 600@600). clearColor ifNotNil:[b3d clearViewport: clearColor]. b3d clearDepthBuffer. "b3d addLight: (B3DAmbientLight color: Color white)." self renderOn: b3d. b3d finish. b3d destroy.! !!B3DScene methodsFor: 'displaying' stamp: 'ar 2/16/1999 05:58'!renderOn: aRenderer defaultCamera ifNotNil:[ defaultCamera setClippingPlanesFrom: self. defaultCamera aspectRatio: aRenderer viewport aspectRatio. defaultCamera renderOn: aRenderer]. lights do:[:light| aRenderer addLight: light]. objects do:[:obj| obj renderOn: aRenderer].! !!B3DScene class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 23:59'!from3DS: aDictionary ^self new from3DS: aDictionary! !!B3DScene class methodsFor: 'instance creation' stamp: 'ar 2/17/1999 05:14'!new ^super new initialize! !!B3DScene class methodsFor: 'instance creation' stamp: 'ti 3/21/2000 15:05'!withoutQuestionsFrom3DS: aDictionary ^self new withoutQuestionsFrom3DS: aDictionary! !Main comment stating the purpose of this class and relevant relationship to other classes.Possible useful expressions for doIt or printIt.Structure: instVar1 type -- comment about the purpose of instVar1 instVar2 type -- comment about the purpose of instVar2Any further useful comments about the general approach of this implementation.!!B3DSceneExplorerMorph methodsFor: 'accessing' stamp: 'ti 3/24/2000 17:16'!scene ^b3DSceneMorph scene! !!B3DSceneExplorerMorph methodsFor: 'accessing' stamp: 'ti 3/24/2000 17:04'!scene: aScene b3DSceneMorph scene: aScene.! !!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'ti 3/21/2000 15:08'!openThreeDSFile | menu result newFileString myScene | menu := StandardFileMenu oldFileMenu: (FileDirectory default). result := menu startUpWithCaption: 'Select 3DS model file ...'. result ifNotNil: [ newFileString := (result directory pathName),(result directory pathNameDelimiter asString),(result name). myScene := (B3DScene withoutQuestionsFrom3DS: (ThreeDSParser parseFileNamed: newFileString)). myScene := self updateSceneWithDefaults: myScene. self scene: myScene. self updateUpVectorForCamera: self scene defaultCamera.].! !!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'ti 3/21/2000 15:11'!selectNewCamera | menu sel | ((self scene cameras isNil) or: [self scene cameras size = 0]) ifTrue: [ (SelectionMenu selections: #('OK')) startUpWithCaption: 'No cameras defined!!'. ^self]. menu _ SelectionMenu selections: self scene cameras keys asArray. sel := menu startUp. sel ifNotNil: [ self scene defaultCamera: (self scene cameras at: sel) copy. self updateUpVectorForCamera: self scene defaultCamera. self changed.]! !!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'ti 3/21/2000 14:28'!selectNewCamera: aCameraString aCameraString ifNotNil: [ self scene defaultCamera: (self scene cameras at: aCameraString) copy. self updateUpVectorForCamera: self scene defaultCamera. self changed.]! !!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'ti 3/24/2000 17:04'!switchRotationStatus b3DSceneMorph switchRotationStatus! !!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'ti 3/24/2000 17:34'!updateSceneWithDefaults: myScene | headLight mat | myScene lights at: 'Ambient1' put: (B3DAmbientLight color: (Color gray: 0.2)). headLight := B3DSpotLight new. headLight position: myScene defaultCamera position. headLight target: myScene defaultCamera target. headLight lightColor: (B3DMaterialColor color: (Color gray: 0.7)). headLight attenuation: (B3DLightAttenuation constant: 1.0 linear: 0.0 squared: 0.0). headLight minAngle: 80. headLight maxAngle: 90. myScene lights at: '$HeadLight$' put: headLight copy. mat := B3DMaterial new. mat diffusePart: (Color gray: 0.25). mat ambientPart: (Color gray: 0.01). myScene objects do: [:o| o material: mat]. ^myScene! !!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'ti 3/21/2000 12:46'!updateUpVectorForCamera: aCamera | oldUp | oldUp := aCamera up. aCamera up: ((aCamera direction cross: oldUp) cross: (aCamera direction))! !!B3DSceneExplorerMorph methodsFor: 'change reporting' stamp: 'ti 3/24/2000 17:11'!layoutChanged | ctrl | super layoutChanged. b3DSceneMorph ifNil: [^self]. b3DSceneMorph extent: (self extent - ((frameWidth * 2)@(frameWidth * 2))). b3DSceneMorph position: (self bounds origin + ((frameWidth)@(frameWidth))). wheels ifNil: [^self]. wheels isEmpty ifTrue: [^self]. ctrl := wheels at: #fov ifAbsent: [nil]. ctrl ifNotNil: [ ctrl position: self bounds corner - ctrl extent - (frameWidth@((frameWidth - ctrl extent y) / 2) rounded)]. ctrl := wheels at: #dolly ifAbsent: [nil]. ctrl ifNotNil: [ ctrl position: self bounds corner - ctrl extent - ((((frameWidth - ctrl extent x) / 2) rounded)@frameWidth)]. ctrl := wheels at: #rotX ifAbsent: [nil]. ctrl ifNotNil: [ ctrl position: (self bounds origin x + (((frameWidth - ctrl extent x) / 2) rounded))@(self bounds corner y - ctrl extent y - frameWidth)]. ctrl := wheels at: #rotY ifAbsent: [nil]. ctrl ifNotNil: [ ctrl position: (self bounds origin x + frameWidth)@(self bounds corner y - ctrl extent y - (((frameWidth - ctrl extent y) / 2) rounded))]. ctrl := wheels at: #rotZ ifAbsent: [nil]. ctrl ifNotNil: [ ctrl position: self bounds origin + ((((frameWidth - ctrl extent x) / 2) rounded)@frameWidth)].! !!B3DSceneExplorerMorph methodsFor: 'drawing' stamp: 'ti 3/24/2000 17:27'!drawOn: aCanvas super drawOn: aCanvas. aCanvas fillRectangle: (self bounds insetBy: frameWidth) color: Color black.! !!B3DSceneExplorerMorph methodsFor: 'event handling' stamp: 'ti 3/24/2000 17:13'!handlesMouseDown: evt ^evt yellowButtonPressed! !!B3DSceneExplorerMorph methodsFor: 'event handling' stamp: 'ti 3/24/2000 17:14'!mouseDown: evt evt yellowButtonPressed ifTrue: [ self yellowButtonMenu. ^super mouseDown: evt].! !!B3DSceneExplorerMorph methodsFor: 'initialization' stamp: 'ti 3/24/2000 17:23'!initialize | ctrl | super initialize. self extent: 300@300. self borderRaised. color := Color gray: 0.8. frameWidth := 25. b3DSceneMorph := AdvancedB3DSceneMorph new. self addMorphFront: b3DSceneMorph. wheels := Dictionary new. ctrl := WheelMorph new. ctrl target: b3DSceneMorph. ctrl actionSelector: #addFovAngle:. ctrl factor: -0.07. ctrl setBalloonText: 'FOV'. self addMorphFront: ctrl. wheels at: #fov put: ctrl. ctrl := WheelMorph new. ctrl target: b3DSceneMorph. ctrl actionSelector: #addDolly:. ctrl factor: 0.005. ctrl beVertical. ctrl setBalloonText: 'Dolly'. self addMorphFront: ctrl. wheels at: #dolly put: ctrl. ctrl := WheelMorph new. ctrl target: b3DSceneMorph. ctrl actionSelector: #rotateZ:. ctrl beVertical. ctrl setBalloonText: 'z Axis'. self addMorphFront: ctrl. wheels at: #rotZ put: ctrl. ctrl := WheelMorph new. ctrl target: b3DSceneMorph. ctrl actionSelector: #rotateY:. ctrl setBalloonText: 'y Axis'. self addMorphFront: ctrl. wheels at: #rotY put: ctrl. ctrl := WheelMorph new. ctrl target: b3DSceneMorph. ctrl actionSelector: #rotateX:. ctrl beVertical. ctrl setBalloonText: 'x Axis'. self addMorphFront: ctrl. wheels at: #rotX put: ctrl.! !!B3DSceneExplorerMorph methodsFor: 'menus' stamp: 'ti 3/22/2000 19:05'!addCustomMenuItems: aCustomMenu (aCustomMenu isKindOf: MenuMorph) ifTrue: [aCustomMenu addUpdating: #rotationString action: #switchRotationStatus] ifFalse: [aCustomMenu add: 'swich rotation status' action: #switchRotationStatus]. aCustomMenu add: 'open 3DS file' action: #openThreeDSFile. aCustomMenu add: 'select new camera' action: #selectNewCamera.! !!B3DSceneExplorerMorph methodsFor: 'menus' stamp: 'ti 3/22/2000 18:51'!addCustomMenuItems: aCustomMenu hand: aHandMorph super addCustomMenuItems: aCustomMenu hand: aHandMorph. aCustomMenu addLine. self addCustomMenuItems: aCustomMenu.! !!B3DSceneExplorerMorph methodsFor: 'menus' stamp: 'ti 3/24/2000 17:04'!rotationString ^b3DSceneMorph isRotating ifTrue: ['stop rotating'] ifFalse: ['start rotating']! !!B3DSceneExplorerMorph methodsFor: 'menus' stamp: 'ti 3/22/2000 18:57'!yellowButtonMenu | menu sel | menu _ CustomMenu new. menu title: self class name. self addCustomMenuItems: menu. sel := menu startUp. sel ifNotNil: [self perform: sel]! !!B3DSceneExplorerMorph methodsFor: 'visual properties' stamp: 'ti 3/21/2000 14:45'!defaultColor ^Color gray! !!B3DSceneMorph methodsFor: 'drawing' stamp: 'ar 5/25/2000 17:57'!debugDraw self fullDrawOn: (Display getCanvas). Display forceToScreen: bounds.! !!B3DSceneMorph methodsFor: 'drawing' stamp: 'ar 2/17/1999 05:05'!drawOn: aCanvas aCanvas asBalloonCanvas render: self.! !!B3DSceneMorph methodsFor: 'drawing' stamp: 'ar 2/17/1999 05:34'!renderOn: aRenderer aRenderer viewport: (self bounds insetBy: 1@1). aRenderer clearDepthBuffer. aRenderer loadIdentity. scene renderOn: aRenderer.! !!B3DSceneMorph methodsFor: 'initialize' stamp: 'ar 2/17/1999 05:27'!createDefaultScene | sceneObj camera | sceneObj _ B3DSceneObject named: 'Sample Cube'. sceneObj geometry: (B3DBox from: (-0.7@-0.7@-0.7) to: (0.7@0.7@0.7)). camera _ B3DCamera new. camera position: 0@0@-1.5. self extent: 100@100. scene _ B3DScene new. scene defaultCamera: camera. scene objects add: sceneObj.! !!B3DSceneMorph methodsFor: 'initialize' stamp: 'ar 2/17/1999 05:24'!initialize super initialize. self createDefaultScene.! !!B3DSceneMorph methodsFor: 'accessing' stamp: 'ar 2/17/1999 05:34'!scene ^scene! !!B3DSceneMorph methodsFor: 'accessing' stamp: 'ar 2/17/1999 05:34'!scene: aScene scene _ aScene! !!B3DSceneMorph methodsFor: 'stepping' stamp: 'ar 2/17/1999 05:31'!step scene defaultCamera rotateBy: 15. self changed.! !!B3DSceneMorph methodsFor: 'stepping' stamp: 'ar 2/17/1999 05:31'!stepTime ^1! !!B3DSceneMorph methodsFor: 'stepping' stamp: 'ar 2/17/1999 05:30'!wantsSteps ^true! !!B3DSceneObject methodsFor: 'initialize' stamp: 'ar 2/16/1999 03:09'!from3DS: aDictionary aDictionary isEmpty ifTrue:[^nil]. geometry _ B3DSTriangleMesh from3DS: aDictionary. material _ (aDictionary at: #triList) last.! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/14/1999 22:37'!boundingBox | bBox | bBox _ geometry ifNotNil:[geometry boundingBox]. children ifNil:[^bBox]. children do:[:obj| bBox _ bBox ifNil:[obj boundingBox] ifNotNil:[bBox merge: obj boundingBox] ]. ^bBox! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:29'!geometry ^geometry! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:30'!geometry: aGeometry geometry _ aGeometry.! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:30'!material ^material! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:10'!material: aMaterial material _ aMaterial. material class == Association ifTrue:[ texture _ material key. material _ material value. ].! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:30'!matrix ^matrix! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:30'!matrix: aMatrix matrix _ aMatrix! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 20:06'!name ^name! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/7/1999 20:06'!name: aString name _ aString.! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:01'!texture ^texture! !!B3DSceneObject methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:01'!texture: aTexture texture _ aTexture! !!B3DSceneObject methodsFor: 'displaying' stamp: 'ar 2/16/1999 03:13'!renderOn: aRenderer material ifNotNil:[ aRenderer pushMaterial. aRenderer material: material]. texture ifNotNil:[ aRenderer pushTexture. aRenderer texture: texture]. matrix ifNotNil:[ aRenderer pushMatrix. aRenderer transformBy: matrix]. geometry ifNotNil:[geometry renderOn: aRenderer]. children ifNotNil:[children do:[:child| child renderOn: aRenderer]]. matrix ifNotNil:[aRenderer popMatrix]. texture ifNotNil:[aRenderer popTexture]. material ifNotNil:[aRenderer popMaterial].! !!B3DSceneObject methodsFor: 'printing' stamp: 'ar 2/8/1999 01:15'!printOn: aStream super printOn: aStream. aStream nextPut:$(; print: self name; nextPut: $).! !!B3DSceneObject class methodsFor: 'instance creation' stamp: 'ar 2/8/1999 01:06'!from3DS: aDictionary ^self new from3DS: aDictionary! !!B3DSceneObject class methodsFor: 'instance creation' stamp: 'ar 2/7/1999 20:06'!named: aString ^self new name: aString! !!B3DShaderPlugin methodsFor: 'primitives' stamp: 'ar 2/17/1999 19:40'!b3dShadeVertexBuffer "Primitive. Shade all the vertices in the vertex buffer using the given array of primitive light sources. Return true on success." | lightArray vtxCount vtxArray lightCount | self export: true. self inline: false. self var: #vtxArray declareC:'float *vtxArray'. vbFlags _ interpreterProxy stackIntegerValue: 0. primMaterial _ self stackMaterialValue: 1. lightArray _ self stackLightArrayValue: 2. vtxCount _ interpreterProxy stackIntegerValue: 3. vtxArray _ self stackPrimitiveVertexArray: 4 ofSize: vtxCount. (vtxArray = nil or:[primMaterial = nil or:[interpreterProxy failed]]) ifTrue:[^interpreterProxy primitiveFail]. "Setup" litVertex _ vtxArray. lightCount _ interpreterProxy slotSizeOf: lightArray. "Go over all vertices" 1 to: vtxCount do:[:i| "Load the primitive vertex" self loadPrimitiveVertex. "Load initial color (e.g., emissive part of vertex and/or material)" (vbFlags anyMask: VBTrackEmission) ifTrue:[ "Load color from vertex" vtxOutColor at: 0 put: (vtxInColor at: 0) + (primMaterial at: EmissionRed). vtxOutColor at: 1 put: (vtxInColor at: 1) + (primMaterial at: EmissionGreen). vtxOutColor at: 2 put: (vtxInColor at: 2) + (primMaterial at: EmissionBlue). vtxOutColor at: 3 put: (vtxInColor at: 3) + (primMaterial at: EmissionAlpha). ] ifFalse:[ vtxOutColor at: 0 put: (primMaterial at: EmissionRed). vtxOutColor at: 1 put: (primMaterial at: EmissionGreen). vtxOutColor at: 2 put: (primMaterial at: EmissionBlue). vtxOutColor at: 3 put: (primMaterial at: EmissionAlpha). ]. "For each enabled light source" 0 to: lightCount-1 do:[:j| "Fetch the light source" primLight _ self fetchLightSource: j ofObject: lightArray. "Setup values" self loadPrimitiveLightSource. "Compute the color from the light source" self shadeVertex. ]. "Store the computed color back" self storePrimitiveVertex. "And step on to the next vertex" litVertex _ litVertex + PrimVertexSize. ]. "Clean up stack" interpreterProxy pop: 6. "Pop args+rcvr" interpreterProxy pushBool: true.! !!B3DShaderPlugin methodsFor: 'primitives' stamp: 'ar 2/17/1999 04:32'!b3dShaderVersion "Return the current shader version." self export: true. self inline: false. interpreterProxy pop: 1. interpreterProxy pushInteger: 1. "Version 1"! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 2/17/1999 19:40'!addPart: lightPart from: materialPart trackFlag: vbTrackFlag scale: scale "Add the given light part to the output color, scaled by the given scale factor. If the given flag is set in vbFlags then load the part from the primitive vertex" | rPart gPart bPart aPart | self var: #lightPart declareC:'float *lightPart'. self var: #materialPart declareC:'float *materialPart'. self var: #scale declareC:'double scale'. self var: #rPart declareC:'double rPart'. self var: #gPart declareC:'double gPart'. self var: #bPart declareC:'double bPart'. self var: #aPart declareC:'double aPart'. self inline: true. (vbFlags anyMask: vbTrackFlag) ifTrue:[ rPart _ (vtxInColor at: 0) * (lightPart at: 0) * scale. gPart _ (vtxInColor at: 1) * (lightPart at: 1) * scale. bPart _ (vtxInColor at: 2) * (lightPart at: 2) * scale. aPart _ (vtxInColor at: 3) * (lightPart at: 3) * scale. ] ifFalse:[ "Note: This should be pre-computed." rPart _ (materialPart at: 0) * (lightPart at: 0) * scale. gPart _ (materialPart at: 1) * (lightPart at: 1) * scale. bPart _ (materialPart at: 2) * (lightPart at: 2) * scale. aPart _ (materialPart at: 3) * (lightPart at: 3) * scale. ]. vtxOutColor at: 0 put: (vtxOutColor at: 0) + rPart. vtxOutColor at: 1 put: (vtxOutColor at: 1) + gPart. vtxOutColor at: 2 put: (vtxOutColor at: 2) + bPart. vtxOutColor at: 3 put: (vtxOutColor at: 3) + aPart.! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 2/17/1999 19:39'!computeAttenuation "Compute the attenuation for the current light and vertex" lightScale _ 1.0. (lightFlags anyMask: FlagAttenuated) ifTrue:[ lightScale _ 1.0 / ((primLight at: PrimLightAttenuationConstant) + (l2vDistance * ((primLight at: PrimLightAttenuationLinear) + (l2vDistance * (primLight at: PrimLightAttenuationSquared)))))].! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:31'!computeDirection "Compute the direction for the current light and vertex" | scale | self inline: true. self var: #scale declareC:'double scale'. (lightFlags anyMask: FlagPositional) ifTrue:[ "Must compute the direction for this vertex" l2vDirection at: 0 put: (litVertex at: PrimVtxPositionX) - (primLight at: PrimLightPositionX). l2vDirection at: 1 put: (litVertex at: PrimVtxPositionY) - (primLight at: PrimLightPositionY). l2vDirection at: 2 put: (litVertex at: PrimVtxPositionZ) - (primLight at: PrimLightPositionZ). "l2vDistance _ self dotProductOf: l2vDirection with: l2vDirection." l2vDistance _ ((l2vDirection at: 0) * (l2vDirection at: 0)) + ((l2vDirection at: 1) * (l2vDirection at: 1)) + ((l2vDirection at: 2) * (l2vDirection at: 2)). (l2vDistance = 0.0 or:[l2vDistance = 1.0]) ifFalse:[ l2vDistance _ l2vDistance sqrt. scale _ -1.0/l2vDistance]. l2vDirection at: 0 put: (l2vDirection at: 0) * scale. l2vDirection at: 1 put: (l2vDirection at: 1) * scale. l2vDirection at: 2 put: (l2vDirection at: 2) * scale. ] ifFalse:[ (lightFlags anyMask: FlagDirectional) ifTrue:[ l2vDirection at: 0 put: (primLight at: PrimLightDirectionX). l2vDirection at: 1 put: (primLight at: PrimLightDirectionY). l2vDirection at: 2 put: (primLight at: PrimLightDirectionZ). ]. ].! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:39'!computeSpecularDirection "Computes l2vSpecDir _ l2vSpecDir - vtx position safelyNormalized. " | scale | self var: #scale declareC:'double scale'. scale _ self inverseLengthOfFloat: litVertex + PrimVtxPosition. l2vSpecDir at: 0 put: (l2vSpecDir at: 0) - ((litVertex at: PrimVtxPositionX) * scale). l2vSpecDir at: 1 put: (l2vSpecDir at: 1) - ((litVertex at: PrimVtxPositionY) * scale). l2vSpecDir at: 2 put: (l2vSpecDir at: 2) - ((litVertex at: PrimVtxPositionZ) * scale).! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:39'!computeSpotFactor "Compute the spot factor for a spot light" | cosAngle minCos deltaCos | self returnTypeC:'double'. self var: #cosAngle declareC:'double cosAngle'. self var: #minCos declareC:'double minCos'. self var: #deltaCos declareC:'double deltaCos'. "Compute cos angle between direction of the spot light and direction to vertex" cosAngle _ self dotProductOfFloat: primLight + PrimLightDirection withDouble: l2vDirection. cosAngle _ 0.0 - cosAngle. minCos _ primLight at: SpotLightMinCos. cosAngle < minCos ifTrue:[^0.0]. deltaCos _ primLight at: SpotLightDeltaCos. deltaCos <= 0.00001 ifTrue:[ "No delta -- a sharp boundary between on and off. Since off has already been determined above, we are on" ^1.0]. "Scale the angle to 0/1 range" cosAngle _ (cosAngle - minCos) / deltaCos. ^cosAngle raisedTo: (primLight at: SpotLightExponent)! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:39'!dotProductOfFloat: v1 withDouble: v2 self var: #v1 declareC:'float * v1'. self var: #v2 declareC:'double *v2'. self returnTypeC:'double'. ^((v1 at: 0) * (v2 at: 0)) + ((v1 at: 1) * (v2 at: 1)) + ((v1 at: 2) * (v2 at: 2)).! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:38'!inverseLengthOfDouble: aVector | scale | self returnTypeC:'double'. self var: #aVector declareC:'double * aVector'. self var: #scale declareC:'double scale'. "scale _ self dotProductOf: aVector with: aVector." scale _ ((aVector at: 0) * (aVector at: 0)) + ((aVector at: 1) * (aVector at: 1)) + ((aVector at: 2) * (aVector at: 2)). (scale = 0.0 or:[scale = 1.0]) ifTrue:[^scale]. ^1.0 / scale sqrt! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:38'!inverseLengthOfFloat: aVector | scale | self returnTypeC:'double'. self var: #aVector declareC:'float * aVector'. self var: #scale declareC:'double scale'. "scale _ self dotProductOf: aVector with: aVector." scale _ ((aVector at: 0) * (aVector at: 0)) + ((aVector at: 1) * (aVector at: 1)) + ((aVector at: 2) * (aVector at: 2)). (scale = 0.0 or:[scale = 1.0]) ifTrue:[^scale]. ^1.0 / scale sqrt! !!B3DShaderPlugin methodsFor: 'shading' stamp: 'ar 4/17/1999 22:40'!shadeVertex | cosAngle specularFactor | self var: #cosAngle declareC:'double cosAngle'. self var: #specularFactor declareC:'double specularFactor'. self computeDirection. self computeAttenuation. (lightFlags anyMask: FlagHasSpot) ifTrue:[ lightScale _ lightScale * self computeSpotFactor. ]. "Compute ambient and diffuse part only if lightScale is non-zero." (lightScale > 0.001) ifTrue:[ "Compute the ambient part" (lightFlags anyMask: FlagAmbientPart) ifTrue:[ self addPart: (primLight + AmbientPart) from: primMaterial + AmbientPart trackFlag: VBTrackAmbient scale: lightScale. ]. "Compute the diffuse part" (lightFlags anyMask: FlagDiffusePart) ifTrue:[ "Compute angle from light->vertex to vertex normal" cosAngle _ self dotProductOfFloat: (litVertex + PrimVtxNormal) withDouble: l2vDirection. "For one-sided lighting negate cosAngle if necessary" ((vbFlags bitAnd: VBTwoSidedLighting) = 0 and:[cosAngle < 0.0]) ifTrue:[cosAngle _ 0.0 - cosAngle]. "For two-sided lighting check if cosAngle > 0.0 meaning that it is a front face" cosAngle > 0.0 ifTrue:[ self addPart: primLight + DiffusePart from: primMaterial + DiffusePart trackFlag: VBTrackDiffuse scale: lightScale * cosAngle. ]. ]. ]. "lightScale > 0.001" "Compute the specular part" ((lightFlags anyMask: FlagSpecularPart) and:[ (primMaterial at: MaterialShininess) > 0.0]) ifTrue:[ "Compute specular part" l2vSpecDir at: 0 put: (l2vDirection at: 0). l2vSpecDir at: 1 put: (l2vDirection at: 1). l2vSpecDir at: 2 put: (l2vDirection at: 2). (vbFlags anyMask: VBUseLocalViewer) ifTrue:[self computeSpecularDirection] ifFalse:[l2vSpecDir at: 2 put: (l2vSpecDir at: 2) - 1.0]. cosAngle _ self dotProductOfFloat: (litVertex + PrimVtxNormal) withDouble: l2vSpecDir. cosAngle > 0.0 ifTrue:[ "Normalize the angle" cosAngle _ cosAngle * (self inverseLengthOfDouble: l2vSpecDir). "cosAngle should be somewhere between 0 and 1. If not, then the vertex normal was not normalized" cosAngle > 1.0 ifTrue:[ specularFactor _ cosAngle raisedTo: (primMaterial at: MaterialShininess). ] ifFalse:[ cosAngle = 0.0 ifTrue:[specularFactor _ 1.0] ifFalse:[specularFactor _ cosAngle raisedTo: (primMaterial at: MaterialShininess)]. ]. self addPart: primLight + SpecularPart from: primMaterial + SpecularPart trackFlag: VBTrackSpecular scale: specularFactor. ]. ].! !!B3DShaderPlugin methodsFor: 'primitive support' stamp: 'ar 2/15/1999 22:33'!fetchLightSource: index ofObject: anArray "Fetch the primitive light source from the given array. Note: No checks are done within here - that happened in stackLightArrayValue:" | lightOop | self inline: true. self returnTypeC:'void*'. lightOop _ interpreterProxy fetchPointer: index ofObject: anArray. ^interpreterProxy firstIndexableField: lightOop! !!B3DShaderPlugin methodsFor: 'primitive support' stamp: 'ar 2/15/1999 22:29'!stackLightArrayValue: stackIndex "Load an Array of B3DPrimitiveLights from the given stack index" | oop array arraySize | self inline: false. array _ interpreterProxy stackObjectValue: stackIndex. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy fetchClassOf: array) = interpreterProxy classArray ifFalse:[^interpreterProxy primitiveFail]. arraySize _ interpreterProxy slotSizeOf: array. 0 to: arraySize-1 do:[:i| oop _ interpreterProxy fetchPointer: i ofObject: array. (interpreterProxy isIntegerObject: oop) ifTrue:[^interpreterProxy primitiveFail]. ((interpreterProxy isWords: oop) and:[(interpreterProxy slotSizeOf: oop) = PrimLightSize]) ifFalse:[^interpreterProxy primitiveFail]. ]. ^array! !!B3DShaderPlugin methodsFor: 'primitive support' stamp: 'ar 2/15/1999 19:22'!stackMaterialValue: stackIndex "Load a B3DMaterial from the given stack index" | oop | self inline: false. self returnTypeC:'void *'. oop _ interpreterProxy stackObjectValue: stackIndex. interpreterProxy failed ifTrue:[^nil]. ((interpreterProxy isWords: oop) and:[(interpreterProxy slotSizeOf: oop) = MaterialSize]) ifTrue:[^interpreterProxy firstIndexableField: oop]. ^nil! !!B3DShaderPlugin methodsFor: 'other' stamp: 'ar 2/17/1999 19:35'!loadPrimitiveLightSource self inline: true. lightFlags _ (self cCoerce: primLight to: 'int*') at: PrimLightFlags.! !!B3DShaderPlugin methodsFor: 'other' stamp: 'ar 2/17/1999 19:40'!loadPrimitiveVertex "Load the necessary values from the current primitive vertex" | rgba | self inline: true. rgba _ (self cCoerce: litVertex to:'int*') at: PrimVtxColor32. vtxInColor at: 2 put: (rgba bitAnd: 255) * (1.0 / 255.0). rgba _ rgba >> 8. vtxInColor at: 1 put: (rgba bitAnd: 255) * (1.0 / 255.0). rgba _ rgba >> 8. vtxInColor at: 0 put: (rgba bitAnd: 255) * (1.0 / 255.0). rgba _ rgba >> 8. vtxInColor at: 3 put: (rgba bitAnd: 255) * (1.0 / 255.0).! !!B3DShaderPlugin methodsFor: 'other' stamp: 'ar 2/17/1999 19:41'!storePrimitiveVertex "Store the computed output color back into the current primitive vertex. Clamp the r,g,b,a part to be in the range 0-255." | r g b a | self inline: true. r _ ((vtxOutColor at: 0) * 255) asInteger. r _ (r min: 255) max: 0. g _ ((vtxOutColor at: 1) * 255) asInteger. g _ (g min: 255) max: 0. b _ ((vtxOutColor at: 2) * 255) asInteger. b _ (b min: 255) max: 0. a _ ((vtxOutColor at: 3) * 255) asInteger. a _ (a min: 255) max: 0. "The following is equal to b + (g << 8) + (r << 16) + (a << 24)" (self cCoerce: litVertex to:'int*') at: PrimVtxColor32 put: b + (g + (r + (a << 8) << 8) << 8). ! !!B3DShaderPlugin class methodsFor: 'translation' stamp: 'ar 5/15/2000 23:13'!declareCVarsIn: cg cg var: #litVertex type: #'float*'. cg var: #primLight type: #'float*'. cg var: #primMaterial type: #'float*'. cg var: #l2vDirection declareC: 'double l2vDirection[3]'. cg var: #l2vSpecDir declareC: 'double l2vSpecDir[3]'. cg var: #vtxInColor declareC: 'double vtxInColor[4]'. cg var: #vtxOutColor declareC: 'double vtxOutColor[4]'. cg var: #l2vDistance type: #'double'. cg var: #lightScale type: #'double'! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:54'!boundingBox ^bBox ifNil:[bBox _ self computeBoundingBox]! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:53'!colorOfVertex: vtx ^vtx color! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:55'!computeBoundingBox | min max | min _ max _ nil. self vertexPositionsDo:[:vtx| min ifNil:[min _ vtx] ifNotNil:[min _ min min: vtx]. max ifNil:[max _ vtx] ifNotNil:[max _ max max: vtx]. ]. ^Rectangle origin: min corner: max! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:54'!faces ^self! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:54'!faces: aCollection ^self shouldNotImplement! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:53'!normalOfVertex: vtx ^vtx normal! !!B3DSimpleMesh methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:54'!texCoordOfVertex: vtx ^vtx texCoord! !!B3DSimpleMesh methodsFor: 'testing' stamp: 'ar 9/14/1999 22:53'!hasTextureCoords 1 to: self size do:[:i| (self at: i) hasTextureCoords ifFalse:[^false]]. ^true! !!B3DSimpleMesh methodsFor: 'testing' stamp: 'ar 9/14/1999 22:52'!hasVertexColors 1 to: self size do:[:i| (self at: i) hasVertexColors ifFalse:[^false]]. ^true! !!B3DSimpleMesh methodsFor: 'enumerating' stamp: 'ar 9/17/1999 12:38'!do: aBlock 1 to: self size do:[:i| aBlock value: (self at: i)]! !!B3DSimpleMesh methodsFor: 'enumerating' stamp: 'ar 9/14/1999 22:02'!trianglesDo: aBlock 1 to: self size do:[:i| (self at: i) trianglesDo: aBlock. ].! !!B3DSimpleMesh methodsFor: 'enumerating' stamp: 'ar 9/14/1999 21:56'!vertexPositionsDo: aBlock 1 to: self size do:[:i| (self at: i) vertexPositionsDo: aBlock. ]! !!B3DSimpleMesh methodsFor: 'converting' stamp: 'ar 9/14/1999 22:26'!asIndexedMesh "Convert the receiver into (the more compact) indexed representation" ^self asIndexedTriangleMesh! !!B3DSimpleMesh methodsFor: 'converting' stamp: 'ar 9/14/1999 22:17'!asIndexedTriangleMesh "Convert the receiver into (the more compact) indexed triangle representation" | map faces face vtx nrm tex col mesh | map _ Dictionary new: (self size * 4). "Need some space for the vertices" faces _ WriteStream on: (B3DIndexedTriangleArray new: self size). self trianglesDo:[:tri| tri assureVertexNormals. face _ B3DIndexedTriangle with: (map at: tri first ifAbsentPut:[map size + 1]) with: (map at: tri second ifAbsentPut:[map size + 1]) with: (map at: tri third ifAbsentPut:[map size + 1]). faces nextPut: face]. faces _ faces contents. vtx _ B3DVector3Array new: map size. nrm _ B3DVector3Array new: map size. self hasTextureCoords ifTrue:[tex _ B3DTexture2Array new: map size]. self hasVertexColors ifTrue:[col _ B3DColor4Array new: map size]. map keysAndValuesDo:[:vertex :idx| vtx at: idx put: vertex position. nrm at: idx put: vertex normal. tex == nil ifFalse:[tex at: idx put: vertex texCoord]. col == nil ifFalse:[col at: idx put: vertex color]. ]. mesh _ B3DIndexedTriangleMesh new. mesh faces: faces. mesh vertices: vtx. mesh texCoords: tex. mesh vertexColors: col. mesh vertexNormals: nrm. ^mesh! !!B3DSimpleMesh methodsFor: 'converting' stamp: 'ar 9/14/1999 22:05'!asSimpleMesh ^self! !!B3DSimpleMesh methodsFor: 'converting' stamp: 'ar 9/17/1999 12:31'!transformedBy: aMatrix "Return a copy of the receiver with its vertices transformed by the given matrix" | newFaces| newFaces _ Array new: self size. 1 to: self size do:[:i| newFaces at: i put: ((self at: i) transformedBy: aMatrix)]. ^self class withAll: newFaces! !!B3DSimpleMesh methodsFor: 'rendering' stamp: 'ar 11/7/1999 18:15'!renderOn: aRenderer | box bounds | box _ nil. 1 to: self size do:[:i| bounds _ (self at: i) renderOn: aRenderer. box == nil ifTrue:[box _ bounds] ifFalse:[box _ box quickMerge: bounds]. ]. ^box! !!B3DSimpleMesh methodsFor: 'private' stamp: 'ar 9/14/1999 23:01'!withAll: aCollection 1 to: self size do:[:i| self at: i put: (aCollection at: i). ].! !!B3DSimpleMesh class methodsFor: 'instance creation' stamp: 'ar 9/14/1999 23:00'!withAll: aCollection ^(self new: aCollection size) withAll: aCollection! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:50'!first ^self at: 1! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:50'!fourth ^self at: 4! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:51'!normal ^normal ifNil:[normal _ self computeFaceNormal].! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:53'!normal: aB3DVector3 normal _ aB3DVector3! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:50'!second ^self at: 2! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 22:50'!third ^self at: 3! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:53'!vertices ^self! !!B3DSimpleMeshFace methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:53'!vertices: aCollection ^self shouldNotImplement.! !!B3DSimpleMeshFace methodsFor: 'testing' stamp: 'ar 9/14/1999 23:05'!hasTextureCoords 1 to: self size do:[:i| (self at: i) hasTextureCoords ifFalse:[^false]]. ^true! !!B3DSimpleMeshFace methodsFor: 'testing' stamp: 'ar 9/14/1999 23:05'!hasVertexColors 1 to: self size do:[:i| (self at: i) hasVertexColors ifFalse:[^false]]. ^true! !!B3DSimpleMeshFace methodsFor: 'enumerating' stamp: 'ar 9/17/1999 12:38'!do: aBlock 1 to: self size do:[:i| aBlock value: (self at: i)]! !!B3DSimpleMeshFace methodsFor: 'enumerating' stamp: 'ar 9/14/1999 22:01'!trianglesDo: aBlock "Evaluate aBlock with triangular faces" | face | self size = 3 ifTrue:[^aBlock value: self]. 3 to: self size do:[:i| face _ self class with: (self at: 1) with: (self at: i-1) with: (self at: i). aBlock value: face].! !!B3DSimpleMeshFace methodsFor: 'enumerating' stamp: 'ar 9/14/1999 21:56'!vertexPositionsDo: aBlock 1 to: self size do:[:i| (self at: i) vertexPositionsDo: aBlock. ]! !!B3DSimpleMeshFace methodsFor: 'rendering' stamp: 'ar 11/7/1999 18:14'!renderOn: aRenderer ^aRenderer drawPolygonAfter:[ aRenderer normal: self normal. 1 to: self size do:[:i| (self at: i) renderOn: aRenderer]. ].! !!B3DSimpleMeshFace methodsFor: 'private' stamp: 'ar 9/14/1999 23:09'!computeFaceNormal | d1 d2 nrml | self size < 3 ifTrue:[^B3DVector3 zero]. d1 _ (self at: 1) position - (self at: 2) position. d2 _ (self at: 3) position - (self at: 2) position. d1 safelyNormalize. d2 safelyNormalize. nrml _ d1 cross: d2. ^nrml safelyNormalize! !!B3DSimpleMeshFace methodsFor: 'private' stamp: 'ar 9/14/1999 22:04'!with: v1 with: v2 with: v3 self at: 1 put: v1; at: 2 put: v2; at: 3 put: v3! !!B3DSimpleMeshFace methodsFor: 'private' stamp: 'ar 9/14/1999 22:04'!with: v1 with: v2 with: v3 with: v4 self at: 1 put: v1; at: 2 put: v2; at: 3 put: v3; at: 4 put: v4! !!B3DSimpleMeshFace methodsFor: 'private' stamp: 'ar 9/14/1999 22:05'!withAll: aCollection 1 to: self size do:[:i| self at: i put: (aCollection at: i). ].! !!B3DSimpleMeshFace methodsFor: 'misc' stamp: 'ar 9/14/1999 22:51'!assureVertexNormals | vtx | 1 to: self size do:[:i| vtx _ self at: i. vtx normal == nil ifTrue:[ vtx _ vtx copy. vtx normal: self normal. self at: i put: vtx]].! !!B3DSimpleMeshFace methodsFor: 'converting' stamp: 'ar 9/17/1999 12:31'!transformedBy: aMatrix "Return a copy of the receiver with its vertices transformed by the given matrix" | newVtx | newVtx _ Array new: self size. 1 to: self size do:[:i| newVtx at: i put: ((self at: i) transformedBy: aMatrix)]. ^self class withAll: newVtx! !!B3DSimpleMeshFace class methodsFor: 'instance creation' stamp: 'ar 9/14/1999 22:03'!with: v0 with: v1 with: v2 ^(self new: 3) with: v0 with: v1 with: v2! !!B3DSimpleMeshFace class methodsFor: 'instance creation' stamp: 'ar 9/14/1999 22:03'!with: v0 with: v1 with: v2 with: v3 ^(self new: 4) with: v0 with: v1 with: v2 with: v3! !!B3DSimpleMeshFace class methodsFor: 'instance creation' stamp: 'ar 9/14/1999 22:03'!withAll: aCollection ^(self new: aCollection size) withAll: aCollection! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:46'!color ^color! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:46'!color: aB3DColor4 color _ aB3DColor4! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:45'!normal ^normal! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:46'!normal: aB3DVector3 normal _ aB3DVector3! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:45'!position ^position! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:45'!position: aB3DVector3 position _ aB3DVector3! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:46'!texCoord ^texCoord! !!B3DSimpleMeshVertex methodsFor: 'accessing' stamp: 'ar 9/14/1999 21:46'!texCoord: aB3DVector2 texCoord _ aB3DVector2! !!B3DSimpleMeshVertex methodsFor: 'testing' stamp: 'ar 9/14/1999 23:06'!hasTextureCoords ^texCoord notNil! !!B3DSimpleMeshVertex methodsFor: 'testing' stamp: 'ar 9/14/1999 23:06'!hasVertexColors ^color notNil! !!B3DSimpleMeshVertex methodsFor: 'comparing' stamp: 'ar 9/14/1999 21:48'!= aVertex ^self class == aVertex class and:[self position = aVertex position and:[self normal = aVertex normal and:[self color = aVertex color and:[self texCoord = aVertex texCoord]]]]! !!B3DSimpleMeshVertex methodsFor: 'comparing' stamp: 'ar 9/14/1999 21:49'!hash "Hash is re-implemented because #= is re-implemented" ^(position hash bitXor: texCoord hash) bitXor: (normal hash bitXor: color hash)! !!B3DSimpleMeshVertex methodsFor: 'enumerating' stamp: 'ar 9/14/1999 21:56'!vertexPositionsDo: aBlock position vertexPositionsDo: aBlock.! !!B3DSimpleMeshVertex methodsFor: 'rendering' stamp: 'ar 9/14/1999 21:59'!renderOn: aRenderer color == nil ifFalse:[aRenderer color: color]. texCoord == nil ifFalse:[aRenderer texCoord: texCoord]. normal == nil ifFalse:[aRenderer normal: normal]. aRenderer vertex: position.! !!B3DSimpleMeshVertex methodsFor: 'printing' stamp: 'ar 9/16/1999 22:48'!printOn: aStream aStream nextPutAll:'['; print: position; nextPutAll:']'.! !!B3DSimpleMeshVertex methodsFor: 'converting' stamp: 'ar 9/17/1999 13:30'!transformedBy: aMatrix "Return a copy of the receiver with its vertices transformed by the given matrix" | transformer copy | transformer _ B3DVertexTransformer new. transformer loadIdentity. transformer transformBy: aMatrix. copy _ self copy. copy position: (transformer transformPosition: position). normal == nil ifFalse:[copy normal: (transformer transformDirection: normal) safelyNormalize]. ^copy! !!B3DSimulRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:45'!clipRect: aRectangle super clipRect: aRectangle. scanner bitBlt clipRect: aRectangle.! !!B3DSimulRasterizer methodsFor: 'initialize' stamp: 'ar 4/18/1999 04:35'!flush self mainLoop.! !!B3DSimulRasterizer methodsFor: 'initialize' stamp: 'ar 4/18/1999 04:36'!initialize super initialize. scanner _ B3DScanner new.! !!B3DSimulRasterizer methodsFor: 'initialize' stamp: 'ar 4/18/1999 04:36'!reset super reset. scanner _ B3DScanner new.! !!B3DSimulRasterizer methodsFor: 'initialize' stamp: 'ar 5/28/2000 12:18'!target: destForm | bb span sourceForm | super target: destForm. span _ Bitmap new: 2048. sourceForm _ Form extent: span size@1 depth: 32 bits: span. bb _ BitBlt current toForm: destForm. bb sourceForm: sourceForm. bb isFXBlt ifTrue:[ bb colorMap: (sourceForm colormapIfNeededFor: destForm). bb combinationRule: 34 "Form paint". "Later we'll change this to 34 for alpha blending" ] ifFalse:[ bb colorMap: (sourceForm colormapIfNeededForDepth: destForm depth). bb combinationRule: 34 "Form paint". "Later we'll change this to 34 for alpha blending" ]. bb destX: 0; destY: 0; sourceX: 0; sourceY: 0; width: 1; height: 1. scanner spanBuffer: span. scanner bitBlt: bb.! !!B3DSimulRasterizer methodsFor: 'testing' stamp: 'ar 4/18/1999 04:36'!needsClip ^true! !!B3DSimulRasterizer methodsFor: 'processing' stamp: 'ar 4/18/1999 04:48'!loadVerticesFrom: vb | out vtxArray | vtxArray _ vb vertexArray. out _ Array new: vb vertexCount. 1 to: vb vertexCount do:[:i| out at: i put: (vtxArray at: i). ]. ^out! !!B3DSimulRasterizer methodsFor: 'processing' stamp: 'ar 4/18/1999 05:31'!mainLoop scanner mainLoop. scanner resetObjects.! !!B3DSimulRasterizer methodsFor: 'processing' stamp: 'ar 4/18/1999 07:34'!processIndexedQuads: vb | vtxArray out idx1 idxArray idx2 idx3 face obj idx4 | vtxArray _ self loadVerticesFrom: vb. idxArray _ vb indexArray. out _ WriteStream on: (B3DIndexedTriangleArray new: vb indexCount // 3 * 2). 1 to: vb indexCount by: 4 do:[:i| idx1 _ idxArray at: i. idx2 _ idxArray at: i+1. idx3 _ idxArray at: i+2. idx4 _ idxArray at: i+3. idx1 = 0 ifFalse:[ face _ B3DIndexedTriangle with: idx1 with: idx2 with: idx3. out nextPut: face. face _ B3DIndexedTriangle with: idx3 with: idx4 with: idx1. out nextPut: face]. ]. obj _ B3DPrimitiveObject new. obj faces: out contents. obj vertices: vtxArray. obj texture: texture. obj mapVertices: viewport. obj setupVertexOrder. obj sortInitialFaces. scanner addObject: obj.! !!B3DSimulRasterizer methodsFor: 'processing' stamp: 'ar 4/18/1999 06:55'!processIndexedTriangles: vb | vtxArray out idx1 idxArray idx2 idx3 face obj | vtxArray _ self loadVerticesFrom: vb. idxArray _ vb indexArray. out _ WriteStream on: (B3DIndexedTriangleArray new: vb indexCount // 3). 1 to: vb indexCount by: 3 do:[:i| idx1 _ idxArray at: i. idx2 _ idxArray at: i+1. idx3 _ idxArray at: i+2. idx1 = 0 ifFalse:[ face _ B3DIndexedTriangle with: idx1 with: idx2 with: idx3. out nextPut: face]. ]. obj _ B3DPrimitiveObject new. obj faces: out contents. obj vertices: vtxArray. obj texture: texture. obj mapVertices: viewport. obj setupVertexOrder. obj sortInitialFaces. scanner addObject: obj.! !!B3DSimulRasterizer methodsFor: 'processing' stamp: 'ar 4/18/1999 07:56'!processPolygon: vb | vtxArray out face obj | vtxArray _ self loadVerticesFrom: vb. out _ WriteStream on: (B3DIndexedTriangleArray new: vtxArray size - 2). 3 to: vb vertexCount do:[:i| face _ B3DIndexedTriangle with: 1 with: i-1 with: i. out nextPut: face. ]. obj _ B3DPrimitiveObject new. obj faces: out contents. obj vertices: vtxArray. obj texture: texture. obj mapVertices: viewport. obj setupVertexOrder. obj sortInitialFaces. scanner addObject: obj.! !!B3DSimulRasterizer class methodsFor: 'testing'!isAvailable ^true "Always"! !!B3DSpotLight methodsFor: 'initialize' stamp: 'ar 2/7/1999 18:44'!from3DS: aDictionary "Initialize the receiver from a 3DS point light" | spotValues hotSpot fallOff | super from3DS: aDictionary. spotValues _ aDictionary at: #spot. target _ spotValues at: #target. hotSpot _ spotValues at: #hotspotAngle. self minAngle: hotSpot. fallOff _ spotValues at: #falloffAngle. self maxAngle: hotSpot + fallOff.! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:18'!direction ^direction ifNil:[direction _ (target - position) safelyNormalize].! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/8/1999 01:40'!direction: aVector direction _ aVector! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:47'!hotSpotDeltaCosine ^deltaCos! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:45'!hotSpotMaxCosine ^maxCos! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:45'!hotSpotMinCosine ^minCos! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:46'!maxAngle ^maxCos arcCos radiansToDegrees! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 20:25'!maxAngle: angle minCos _ angle degreesToRadians cos. maxCos ifNotNil:[deltaCos _ maxCos - minCos].! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 18:46'!minAngle ^minCos arcCos radiansToDegrees! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 20:25'!minAngle: angle maxCos _ angle degreesToRadians cos. minCos ifNotNil:[deltaCos _ maxCos - minCos].! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 20:16'!target ^target! !!B3DSpotLight methodsFor: 'accessing' stamp: 'ar 2/7/1999 20:16'!target: aVector target _ aVector! !!B3DSpotLight methodsFor: 'testing' stamp: 'ar 2/15/1999 02:18'!hasSpot ^true! !!B3DSpotLight methodsFor: 'converting' stamp: 'ar 2/15/1999 22:01'!asPrimitiveLight "Convert the receiver into a B3DPrimitiveLight" | primLight | primLight _ super asPrimitiveLight. primLight flags: (primLight flags bitOr: FlagHasSpot). primLight spotMinCos: minCos. primLight spotMaxCos: maxCos. primLight spotDeltaCos: deltaCos. primLight spotExponent: self spotExponent. primLight direction: (target - position) safelyNormalize. ^primLight! !!B3DSpotLight methodsFor: 'converting' stamp: 'ar 2/8/1999 01:39'!transformedBy: aTransformer ^(super transformedBy: aTransformer) target: (aTransformer transformPosition: target); direction: nil! !I represent a simple 2D texture.Instance variables: wrap <Boolean> If true, wrap the texture - otherwise clamp it. interpolate <Boolean> If true, interpolate the pixels of the texture. envMode <Integer> How we combine colors with the texture. Possible values: 0 - OpenGL style modulate texture 1 - OpenGL style decal texture!!B3DTexture methodsFor: 'accessing' stamp: 'ar 6/9/2000 19:16'!contentsOfArea: aRect "Return a new form which derives from the portion of the original form delineated by aRect." ^self contentsOfArea: aRect into: ((self class extent: aRect extent depth: depth) wrap: self wrap; envMode: self envMode; interpolate: self interpolate; yourself)! !!B3DTexture methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:36'!envMode ^envMode! !!B3DTexture methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:36'!envMode: aNumber envMode _ aNumber.! !!B3DTexture methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:33'!interpolate ^interpolate! !!B3DTexture methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:34'!interpolate: aBool interpolate _ aBool! !!B3DTexture methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:34'!wrap ^wrap! !!B3DTexture methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:33'!wrap: aBool wrap _ aBool! !!B3DTexture methodsFor: 'flipping' stamp: 'jsp 3/15/1999 14:20'!flipVertically "Flip the texture vertically" | temp h w row | h _ self height. w _ self width. 0 to: ((h // 2) - 1) do: [:i | row _ h - i - 1. 1 to: w do: [:j | temp _ bits at: ((i * w) + j). bits at: ((i * w) + j) put: (bits at: ((row * w) + j)). bits at: ((row * w) + j) put: temp. ]. ].! !!B3DTexture methodsFor: 'converting' stamp: 'ar 5/27/1999 17:49'!asTexture ^self! !!B3DTexture2Array methodsFor: 'accessing' stamp: 'ar 2/6/1999 23:30'!at: index put: value value isPoint ifTrue:[super at: index put: (B3DVector2 u: value x v: value y)] ifFalse:[super at: index put: value]. ^value! !!B3DTexture2Array class methodsFor: 'accessing' stamp: 'ar 2/6/1999 23:31'!contentsClass ^B3DVector2! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 5/22/2000 17:12'!b3dInplaceHouseHolderInvert "Primitive. Perform an inplace house holder matrix inversion" | rcvr d x sigma beta sum s m | self export: true. self var: #rcvr declareC:'float *rcvr'. self var: #m declareC:'double m[4][4]'. self var: #x declareC:'double x[4][4] = { {1, 0, 0, 0}, {0, 1, 0, 0}, {0, 0, 1, 0}, {0, 0, 0, 1} }'. self var: #d declareC:'double d[4][4]'. self var: #sigma declareC:'double sigma'. self var: #beta declareC:'double beta'. self var: #sum declareC:'double sum'. self var: #s declareC:'double s'. self cCode:'' inSmalltalk:[ m _ CArrayAccessor on: ((1 to: 4) collect:[:i| CArrayAccessor on: (Array new: 4)]). x _ CArrayAccessor on: (Array with: (CArrayAccessor on: #(1.0 0.0 0.0 0.0) copy) with: (CArrayAccessor on: #(0.0 1.0 0.0 0.0) copy) with: (CArrayAccessor on: #(0.0 0.0 1.0 0.0) copy) with: (CArrayAccessor on: #(0.0 0.0 0.0 1.0) copy)). d _ CArrayAccessor on: ((1 to: 4) collect:[:i| CArrayAccessor on: (Array new: 4)]). ]. rcvr _ self stackMatrix: 0. 0 to: 3 do:[:i| 0 to: 3 do:[:j| (m at: i) at: j put: (rcvr at: i*4+j)]]. 0 to: 3 do:[:j| sigma := 0.0. j to: 3 do:[:i| sigma := sigma + (((m at: i) at: j) * ((m at: i) at: j))]. sigma < 1.0e-10 ifTrue:[^interpreterProxy primitiveFail]. "matrix is singular" (((m at: j) at: j) < 0.0) ifTrue:[ s:= sigma sqrt] ifFalse:[ s:= 0.0 - sigma sqrt]. 0 to: 3 do:[:r| (d at: j) at: r put: s]. beta := 1.0 / ( s * ((m at: j) at: j) - sigma). (m at: j) at: j put: (((m at: j) at: j) - s). "update remaining columns" j+1 to: 3 do:[:k| sum := 0.0. j to: 3 do:[:i| sum := sum + (((m at: i) at: j) * ((m at: i) at: k))]. sum := sum * beta. j to: 3 do:[:i| (m at: i) at: k put: (((m at: i) at: k) + (((m at: i) at: j) * sum))]]. "update vector" 0 to: 3 do:[:r| sum := 0.0. j to: 3 do:[:i| sum _ sum + (((x at: i) at: r) * ((m at: i) at: j))]. sum := sum * beta. j to: 3 do:[:i| (x at: i) at: r put:(((x at: i) at: r) + (sum * ((m at: i) at: j)))]. ]. ]. "Now calculate result" 0 to: 3 do:[:r| 3 to: 0 by: -1 do:[:i| i+1 to: 3 do:[:j| (x at: i) at: r put: (((x at: i) at: r) - (((x at: j) at: r) * ((m at: i) at: j))) ]. (x at: i) at: r put: (((x at: i) at: r) / ((d at: i) at: r))]. ]. 0 to: 3 do:[:i| 0 to: 3 do:[:j| rcvr at: i*4+j put: (self cCoerce: ((x at: i) at: j) to:'float')]]. "Return receiver"! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 2/14/1999 00:02'!b3dTransformMatrixWithInto "Transform two matrices into the third" | m1 m2 m3 | self export: true. self inline: false. self var: #m1 declareC:'float *m1'. self var: #m2 declareC:'float *m2'. self var: #m3 declareC:'float *m3'. m3 _ self stackMatrix: 0. m2 _ self stackMatrix: 1. m1 _ self stackMatrix: 2. (m1 = nil) | (m2 = nil) | (m3 = nil) ifTrue:[^interpreterProxy primitiveFail]. m2 == m3 ifTrue:[^interpreterProxy primitiveFail]. self transformMatrix: m1 with: m2 into: m3. interpreterProxy pop: 3. "Leave rcvr on stack"! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 2/14/1999 00:03'!b3dTransformPrimitiveNormal "Transform the normal of the given primitive vertex using the argument matrix and rescale the normal if necessary." | pVertex matrix rescale | self export: true. self inline: false. self var: #matrix declareC:'float *matrix'. self var: #pVertex declareC:'float *pVertex'. rescale _ interpreterProxy stackValue: 0. rescale == interpreterProxy nilObject ifFalse:[rescale _ interpreterProxy booleanValueOf: rescale]. matrix _ self stackMatrix: 1. pVertex _ self stackPrimitiveVertex: 2. (matrix = nil) | (pVertex = nil) ifTrue:[^interpreterProxy primitiveFail]. (rescale ~~ true and:[rescale ~~ false]) ifTrue:[rescale _ self analyzeMatrix3x3Length: matrix]. self transformPrimitiveNormal: pVertex by: matrix rescale: rescale. interpreterProxy pop: 3. "Leave rcvr on stack"! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 2/14/1999 00:03'!b3dTransformPrimitivePosition "Transform the position of the given primitive vertex the given matrix and store the result back inplace." | pVertex matrix | self export: true. self inline: false. self var: #matrix declareC:'float *matrix'. self var: #pVertex declareC:'float *pVertex'. matrix _ self stackMatrix: 0. pVertex _ self stackPrimitiveVertex: 1. (matrix = nil) | (pVertex = nil) ifTrue:[^interpreterProxy primitiveFail]. self transformPrimitivePosition: pVertex by: matrix. interpreterProxy pop: 2. "Leave rcvr on stack"! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 2/14/1999 00:03'!b3dTransformPrimitiveRasterPosition "Transform the position of the given primitive vertex the given matrix and store the result in homogenous coordinates at rasterPos." | pVertex matrix | self export: true. self inline: false. self var: #matrix declareC:'float *matrix'. self var: #pVertex declareC:'float *pVertex'. matrix _ self stackMatrix: 0. pVertex _ self stackPrimitiveVertex: 1. (matrix = nil) | (pVertex = nil) ifTrue:[^interpreterProxy primitiveFail]. self transformPrimitiveRasterPosition: pVertex by: matrix. interpreterProxy pop: 2. "Leave rcvr on stack"! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 2/14/1999 00:05'!b3dTransformVertexBuffer "Transform an entire vertex buffer using the supplied modelview and projection matrix." | flags projectionMatrix modelViewMatrix vtxCount vtxArray | self export: true. self inline: false. self var: #projectionMatrix declareC:'float *projectionMatrix'. self var: #modelViewMatrix declareC:'float *modelViewMatrix'. self var: #vtxArray declareC:'float *vtxArray'. flags _ interpreterProxy stackIntegerValue: 0. projectionMatrix _ self stackMatrix: 1. modelViewMatrix _ self stackMatrix: 2. vtxCount _ interpreterProxy stackIntegerValue: 3. vtxArray _ self stackPrimitiveVertexArray: 4 ofSize: vtxCount. (projectionMatrix = nil) | (modelViewMatrix = nil) | (vtxArray = nil) ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy failed ifTrue:[^nil]. self transformVB: vtxArray count: vtxCount by: modelViewMatrix and: projectionMatrix flags: flags. interpreterProxy pop: 5. "Leave rcvr on stack"! !!B3DTransformerPlugin methodsFor: 'primitives' stamp: 'ar 2/17/1999 04:31'!b3dTransformerVersion "Return the current version of the transformer" self export: true. self inline: false. interpreterProxy pop: 1. interpreterProxy pushInteger: 1. "Version 1"! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 2/13/1999 23:45'!analyzeMatrix3x3Length: m "Check if the matrix scales normals to non-unit length." | det | self var: #m declareC:'float *m'. self var: #det declareC:'double det'. det _ ((m at: 0) * (m at: 5) * (m at: 10)) - ((m at: 2) * (m at: 5) * (m at: 8)) + ((m at: 4) * (m at: 9) * (m at: 2)) - ((m at: 6) * (m at: 9) * (m at: 0)) + ((m at: 8) * (m at: 1) * (m at: 6)) - ((m at: 10) * (m at: 1) * (m at: 4)). ^det < 0.99 or:[det > 1.01]! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 2/13/1999 23:45'!analyzeMatrix: m "Analyze the matrix and return the appropriate flags" | flags | self var: #m declareC:'float *m'. "Check the perspective" flags _ 0. ((m at: 12) = 0.0 and:[(m at: 13) = 0.0 and:[(m at: 14) = 0.0 and:[(m at: 15) = 1.0]]]) ifTrue:[ flags _ flags bitOr: FlagM44NoPerspective. "Check translation" ((m at: 3) = 0.0 and:[(m at: 7) = 0.0 and:[(m at: 11) = 0.0]]) ifTrue:[ flags _ flags bitOr: FlagM44NoTranslation. "Check for identity" ((m at: 0) = 1.0 and:[(m at: 5) = 1.0 and:[(m at: 10) = 1.0 and:[ (m at: 1) = 0.0 and:[(m at: 2) = 0.0 and:[ (m at: 4) = 0.0 and:[(m at: 6) = 0.0 and:[ (m at: 8) = 0.0 and:[(m at: 9) = 0.0]]]]]]]]) ifTrue:[ flags _ flags bitOr: FlagM44Identity. ]. ]. ]. ^flags! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 2/13/1999 23:45'!transformMatrix: src with: arg into: dst "Transform src with arg into dst. It is allowed that src == dst but not arg == dst" | m1 m2 m3 c1 c2 c3 c4 | self var: #src declareC:'float *src'. self var: #arg declareC:'float *arg'. self var: #dst declareC:'float *dst'. self var: #m1 declareC:'float *m1'. self var: #m2 declareC:'float *m2'. self var: #m3 declareC:'float *m3'. self var: #c1 declareC:'float c1'. self var: #c2 declareC:'float c2'. self var: #c3 declareC:'float c3'. self var: #c4 declareC:'float c4'. m1 _ self cCoerce: src to:'float *'. m2 _ self cCoerce: arg to: 'float *'. m3 _ self cCoerce: dst to: 'float *'. 0 to: 3 do:[:i| "Compute next row" c1 _ ((m1 at: 0) * (m2 at: 0)) + ((m1 at: 1) * (m2 at: 4)) + ((m1 at: 2) * (m2 at: 8)) + ((m1 at: 3) * (m2 at: 12)). c2 _ ((m1 at: 0) * (m2 at: 1)) + ((m1 at: 1) * (m2 at: 5)) + ((m1 at: 2) * (m2 at: 9)) + ((m1 at: 3) * (m2 at: 13)). c3 _ ((m1 at: 0) * (m2 at: 2)) + ((m1 at: 1) * (m2 at: 6)) + ((m1 at: 2) * (m2 at: 10)) + ((m1 at: 3) * (m2 at: 14)). c4 _ ((m1 at: 0) * (m2 at: 3)) + ((m1 at: 1) * (m2 at: 7)) + ((m1 at: 2) * (m2 at: 11)) + ((m1 at: 3) * (m2 at: 15)). "Store result" m3 at: 0 put: c1. m3 at: 1 put: c2. m3 at: 2 put: c3. m3 at: 3 put: c4. "Skip src and dst to next row" m1 _ m1 + 4. m3 _ m3 + 4. ].! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 4/17/1999 22:22'!transformPrimitiveNormal: pVertex by: matrix rescale: rescale "Transform the normal of the given primitive vertex" | x y z rx ry rz dot | self var: #pVertex declareC:'float *pVertex'. self var: #matrix declareC:'float *matrix'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #rx declareC:'double rx'. self var: #ry declareC:'double ry'. self var: #rz declareC:'double rz'. self var: #dot declareC:'double dot'. x _ pVertex at: PrimVtxNormalX. y _ pVertex at: PrimVtxNormalY. z _ pVertex at: PrimVtxNormalZ. rx _ (x * (matrix at: 0)) + (y * (matrix at: 1)) + (z * (matrix at: 2)). ry _ (x * (matrix at: 4)) + (y * (matrix at: 5)) + (z * (matrix at: 6)). rz _ (x * (matrix at: 8)) + (y * (matrix at: 9)) + (z * (matrix at: 10)). rescale ifTrue:[ dot _ (rx * rx) + (ry * ry) + (rz * rz). dot < 1.0e-20 ifTrue:[rx _ ry _ rz _ 0.0] ifFalse:[dot = 1.0 ifFalse:[dot _ 1.0 / dot sqrt. rx _ rx * dot. ry _ ry * dot. rz _ rz * dot]]]. pVertex at: PrimVtxNormalX put: (self cCoerce: rx to:'float'). pVertex at: PrimVtxNormalY put: (self cCoerce: ry to:'float'). pVertex at: PrimVtxNormalZ put: (self cCoerce: rz to:'float').! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 4/17/1999 22:24'!transformPrimitivePosition: pVertex by: matrix "Transform the normal of the given primitive vertex" | x y z rx ry rz rw | self var: #pVertex declareC:'float *pVertex'. self var: #matrix declareC:'float *matrix'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #rx declareC:'double rx'. self var: #ry declareC:'double ry'. self var: #rz declareC:'double rz'. self var: #rw declareC:'double rw'. x _ pVertex at: PrimVtxPositionX. y _ pVertex at: PrimVtxPositionY. z _ pVertex at: PrimVtxPositionZ. rx _ (x * (matrix at: 0)) + (y * (matrix at: 1)) + (z * (matrix at: 2)) + (matrix at: 3). ry _ (x * (matrix at: 4)) + (y * (matrix at: 5)) + (z * (matrix at: 6)) + (matrix at: 7). rz _ (x * (matrix at: 8)) + (y * (matrix at: 9)) + (z * (matrix at: 10)) + (matrix at: 11). rw _ (x * (matrix at: 12)) + (y * (matrix at: 13)) + (z * (matrix at: 14)) + (matrix at: 15). rw = 1.0 ifTrue:[ pVertex at: PrimVtxPositionX put: (self cCoerce: rx to: 'float'). pVertex at: PrimVtxPositionY put: (self cCoerce: ry to:'float'). pVertex at: PrimVtxPositionZ put: (self cCoerce: rz to: 'float'). ] ifFalse:[ rw = 0.0 ifTrue:[rw _ 0.0] ifFalse:[rw _ 1.0 / rw]. pVertex at: PrimVtxPositionX put: (self cCoerce: rx*rw to:'float'). pVertex at: PrimVtxPositionY put: (self cCoerce: ry*rw to:'float'). pVertex at: PrimVtxPositionZ put: (self cCoerce: rz*rw to: 'float'). ].! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 4/17/1999 22:24'!transformPrimitivePositionFast: pVertex by: matrix "Transform the position of the given primitive vertex assuming that matrix a41 = a42 = a43 = 0.0 and a44 = 1.0" | x y z rx ry rz | self var: #pVertex declareC:'float *pVertex'. self var: #matrix declareC:'float *matrix'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #rx declareC:'double rx'. self var: #ry declareC:'double ry'. self var: #rz declareC:'double rz'. x _ pVertex at: PrimVtxPositionX. y _ pVertex at: PrimVtxPositionY. z _ pVertex at: PrimVtxPositionZ. rx _ (x * (matrix at: 0)) + (y * (matrix at: 1)) + (z * (matrix at: 2)) + (matrix at: 3). ry _ (x * (matrix at: 4)) + (y * (matrix at: 5)) + (z * (matrix at: 6)) + (matrix at: 7). rz _ (x * (matrix at: 8)) + (y * (matrix at: 9)) + (z * (matrix at: 10)) + (matrix at: 11). pVertex at: PrimVtxPositionX put: (self cCoerce: rx to: 'float'). pVertex at: PrimVtxPositionY put: (self cCoerce: ry to: 'float'). pVertex at: PrimVtxPositionZ put: (self cCoerce: rz to: 'float').! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 4/17/1999 22:25'!transformPrimitivePositionFaster: pVertex by: matrix "Transform the position of the given primitive vertex assuming that matrix a14 = a24 = a34 = a41 = a42 = a43 = 0.0 and a44 = 1.0" | x y z rx ry rz | self var: #pVertex declareC:'float *pVertex'. self var: #matrix declareC:'float *matrix'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #rx declareC:'double rx'. self var: #ry declareC:'double ry'. self var: #rz declareC:'double rz'. x _ pVertex at: PrimVtxPositionX. y _ pVertex at: PrimVtxPositionY. z _ pVertex at: PrimVtxPositionZ. rx _ (x * (matrix at: 0)) + (y * (matrix at: 1)) + (z * (matrix at: 2)). ry _ (x * (matrix at: 4)) + (y * (matrix at: 5)) + (z * (matrix at: 6)). rz _ (x * (matrix at: 8)) + (y * (matrix at: 9)) + (z * (matrix at: 10)). pVertex at: PrimVtxPositionX put: (self cCoerce: rx to:'float'). pVertex at: PrimVtxPositionY put: (self cCoerce: ry to:'float'). pVertex at: PrimVtxPositionZ put: (self cCoerce: rz to: 'float').! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 4/17/1999 22:26'!transformPrimitiveRasterPosition: pVertex by: matrix "Transform the normal of the given primitive vertex" | x y z rx ry rz rw | self var: #pVertex declareC:'float *pVertex'. self var: #matrix declareC:'float *matrix'. self var: #x declareC:'double x'. self var: #y declareC:'double y'. self var: #z declareC:'double z'. self var: #rx declareC:'double rx'. self var: #ry declareC:'double ry'. self var: #rz declareC:'double rz'. self var: #rw declareC:'double rw'. x _ pVertex at: PrimVtxPositionX. y _ pVertex at: PrimVtxPositionY. z _ pVertex at: PrimVtxPositionZ. rx _ (x * (matrix at: 0)) + (y * (matrix at: 1)) + (z * (matrix at: 2)) + (matrix at: 3). ry _ (x * (matrix at: 4)) + (y * (matrix at: 5)) + (z * (matrix at: 6)) + (matrix at: 7). rz _ (x * (matrix at: 8)) + (y * (matrix at: 9)) + (z * (matrix at: 10)) + (matrix at: 11). rw _ (x * (matrix at: 12)) + (y * (matrix at: 13)) + (z * (matrix at: 14)) + (matrix at: 15). pVertex at: PrimVtxRasterPosX put: (self cCoerce: rx to:'float'). pVertex at: PrimVtxRasterPosY put: (self cCoerce: ry to:'float'). pVertex at: PrimVtxRasterPosZ put: (self cCoerce: rz to:'float'). pVertex at: PrimVtxRasterPosW put: (self cCoerce: rw to:'float').! !!B3DTransformerPlugin methodsFor: 'transforming' stamp: 'ar 2/13/1999 23:47'!transformVB: vtxArray count: vtxCount by: modelViewMatrix and: projectionMatrix flags: flags "Transform the entire vertex array by the given matrices" "TODO: Check the actual trade-offs between vtxCount and analyzing" | mvFlags prFlags pVertex hasNormals rescale | self var: #projectionMatrix declareC:'float *projectionMatrix'. self var: #modelViewMatrix declareC:'float *modelViewMatrix'. self var: #vtxArray declareC:'float *vtxArray'. self var: #pVertex declareC:'float *pVertex'. "Analyze the matrices for better performance" mvFlags _ self analyzeMatrix: modelViewMatrix. prFlags _ self analyzeMatrix: projectionMatrix. pVertex _ self cCoerce: vtxArray to: 'float *'. hasNormals _ flags anyMask: VBVtxHasNormals. "Check if we have to rescale the normals" hasNormals ifTrue:[ (mvFlags anyMask: FlagM44Identity) ifTrue:[rescale _ false] ifFalse:[rescale _ self analyzeMatrix3x3Length: modelViewMatrix]]. "<---- NOTE: The most likely case goes first ---->" ((mvFlags anyMask: FlagM44NoPerspective) and:[prFlags = 0]) ifTrue:[ "Modelview matrix has no perspective part and projection is not optimized" (mvFlags = FlagM44NoTranslation) = 0 ifTrue:[ "Modelview matrix with translation" 1 to: vtxCount do:[:i| hasNormals ifTrue:[self transformPrimitiveNormal: pVertex by: modelViewMatrix rescale: rescale]. self transformPrimitivePositionFast: pVertex by: modelViewMatrix. self transformPrimitiveRasterPosition: pVertex by: projectionMatrix. pVertex _ pVertex + PrimVertexSize]. ] ifFalse:[ "Modelview matrix without translation" 1 to: vtxCount do:[:i| hasNormals ifTrue:[self transformPrimitiveNormal: pVertex by: modelViewMatrix rescale: rescale]. self transformPrimitivePositionFaster: pVertex by: modelViewMatrix. self transformPrimitiveRasterPosition: pVertex by: projectionMatrix. pVertex _ pVertex + PrimVertexSize]. ]. ^nil]. "done" "<---- End of most likely case ---->" ((mvFlags bitAnd: prFlags) anyMask: FlagM44Identity) ifTrue:[ "If both are identity matrices just copy entries" 1 to: vtxCount do:[:i| pVertex at: PrimVtxRasterPosX put: (pVertex at: PrimVtxPositionX). pVertex at: PrimVtxRasterPosY put: (pVertex at: PrimVtxPositionY). pVertex at: PrimVtxRasterPosZ put: (pVertex at: PrimVtxPositionZ). pVertex at: PrimVtxRasterPosW put: 1.0. pVertex _ pVertex + PrimVertexSize]. ^nil]."done" (mvFlags anyMask: FlagM44Identity) ifTrue:[ "If model view matrix is identity just perform projection" 1 to: vtxCount do:[:i| self transformPrimitiveRasterPosition: pVertex by: projectionMatrix. pVertex _ pVertex + PrimVertexSize]. ^nil]. "done" "<--- modelview matrix not identity --->" (prFlags anyMask: FlagM44Identity) ifTrue:[ "If projection matrix is identity just transform and copy. Note: This case is not very likely so it's not been unrolled." 1 to: vtxCount do:[:i| hasNormals ifTrue:[self transformPrimitiveNormal: pVertex by: modelViewMatrix rescale: rescale]. mvFlags = (FlagM44NoPerspective + FlagM44NoPerspective) ifTrue:[ self transformPrimitivePositionFaster: pVertex by: modelViewMatrix. ] ifFalse:[mvFlags = FlagM44NoPerspective ifTrue:[ self transformPrimitivePositionFast: pVertex by: modelViewMatrix. ] ifFalse:[ self transformPrimitivePosition: pVertex by: modelViewMatrix. ]]. pVertex at: PrimVtxRasterPosX put: (pVertex at: PrimVtxPositionX). pVertex at: PrimVtxRasterPosY put: (pVertex at: PrimVtxPositionY). pVertex at: PrimVtxRasterPosZ put: (pVertex at: PrimVtxPositionZ). pVertex at: PrimVtxRasterPosW put: 1.0. pVertex _ pVertex + PrimVertexSize]. ^nil]. "done" "<----- None of the matrices is identity ---->" "Generic transformation" 1 to: vtxCount do:[:i| hasNormals ifTrue:[self transformPrimitiveNormal: pVertex by: modelViewMatrix rescale: rescale]. self transformPrimitivePosition: pVertex by: modelViewMatrix. self transformPrimitiveRasterPosition: pVertex by: projectionMatrix. pVertex _ pVertex + PrimVertexSize].! !I represent simple 2D coordinates in the Balloon 3D framework. I may be used to represent both, 2D points and 2D texture coordinates. !!B3DVector2 methodsFor: 'initialize' stamp: 'ar 2/6/1999 23:30'!u: uValue v: vValue self u: uValue. self v: vValue.! !!B3DVector2 methodsFor: 'initialize' stamp: 'ar 5/4/2000 15:50'!x: uValue y: vValue self x: uValue. self y: vValue.! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 2/6/1999 23:26'!u ^self floatAt: 1! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 2/6/1999 23:27'!u: aFloat self floatAt: 1 put: aFloat! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 2/6/1999 23:27'!v ^self floatAt: 2! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 2/6/1999 23:27'!v: aFloat self floatAt: 2 put: aFloat! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 2/7/1999 02:58'!x ^self at: 1! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 5/4/2000 16:00'!x: aFloat self floatAt: 1 put: aFloat! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 2/7/1999 02:58'!y ^self at: 2! !!B3DVector2 methodsFor: 'accessing' stamp: 'ar 5/4/2000 16:00'!y: aFloat self floatAt: 2 put: aFloat! !!B3DVector2 methodsFor: 'converting' stamp: 'ar 2/13/1999 20:03'!asPoint ^self x @ self y! !!B3DVector2 class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 23:31'!numElements ^2! !!B3DVector2 class methodsFor: 'instance creation' stamp: 'ar 2/6/1999 23:31'!u: uValue v: vValue ^self new u: uValue v: vValue! !!B3DVector2 class methodsFor: 'instance creation' stamp: 'ar 5/4/2000 15:49'!x: uValue y: vValue ^self new x: uValue y: vValue! !!B3DVector2Array class methodsFor: 'instance creation' stamp: 'ar 5/4/2000 15:59'!contentsClass ^B3DVector2! !I represent simple 3D coordinates, used throughout the entire Balloon 3D engine.!!B3DVector3 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:24'!x ^self at: 1! !!B3DVector3 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:24'!x: aFloat self at: 1 put: aFloat! !!B3DVector3 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:24'!y ^self at: 2! !!B3DVector3 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:24'!y: aFloat self at: 2 put: aFloat! !!B3DVector3 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:24'!z ^self at: 3! !!B3DVector3 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:24'!z: aFloat self at: 3 put: aFloat! !!B3DVector3 methodsFor: 'vector functions'!cross: aVector "calculate the cross product from the receiver with aVector" ^self species x: self y * aVector z - (aVector y * self z) y: self z * aVector x - (aVector z * self x) z: self x * aVector y - (aVector x * self y)! !!B3DVector3 methodsFor: 'vector functions'!length: newLength self safelyNormalize *= newLength! !!B3DVector3 methodsFor: 'vector functions' stamp: 'ar 2/6/1999 00:32'!max: aVector ^B3DVector3 x: (self x max: aVector x) y: (self y max: aVector y) z: (self z max: aVector z)! !!B3DVector3 methodsFor: 'vector functions' stamp: 'ar 2/6/1999 00:31'!min: aVector ^B3DVector3 x: (self x min: aVector x) y: (self y min: aVector y) z: (self z min: aVector z)! !!B3DVector3 methodsFor: 'vector functions'!normalize self /= self length! !!B3DVector3 methodsFor: 'vector functions'!normalized ^self / self length! !!B3DVector3 methodsFor: 'vector functions' stamp: 'ar 2/7/1999 00:43'!safelyNormalize "Safely normalize the receiver, e.g. check if the length is non-zero" | length | length _ self length. length = 1.0 ifTrue:[^self]. length = 0.0 ifFalse:[self /= length].! !!B3DVector3 methodsFor: 'vector functions'!safelyNormalized "Safely normalize the receiver, e.g. check if the length is non-zero" ^self copy safelyNormalize! !!B3DVector3 methodsFor: 'vector functions'!squaredLength: newLength self length: newLength sqrt! !!B3DVector3 methodsFor: 'private'!privateLoadFrom: srcObject self x: srcObject x y: srcObject y z: srcObject z.! !!B3DVector3 methodsFor: 'initialize'!x: x y: y z: z self x: x. self y: y. self z: z.! !!B3DVector3 methodsFor: 'converting' stamp: 'ar 2/6/1999 00:06'!asB3DVector3 ^self! !!B3DVector3 methodsFor: 'converting' stamp: 'ar 2/6/1999 00:07'!asB3DVector4 ^B3DVector4 x: self x y: self y z: self z w: 1.0! !!B3DVector3 methodsFor: 'interpolating' stamp: 'jsp 2/9/1999 11:17'!interpolateTo: end at: amountDone "Interpolates a new vector based on the instance vector, the end state vector, and the amount already done (between 0 and 1)." | tX tY tZ | tX _ self x. tY _ self y. tZ _ self z. ^ (B3DVector3 x: (tX + (((end x) - tX) * amountDone)) y: (tY + (((end y) - tY) * amountDone)) z: (tZ + (((end z) - tZ) * amountDone))).! !!B3DVector3 methodsFor: 'testing' stamp: 'laza 3/16/2000 16:30'!isZero ^self = B3DVector3 zero! !!B3DVector3 class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:23'!numElements ^3! !!B3DVector3 class methodsFor: 'instance creation' stamp: 'ar 2/15/1999 02:56'!value: aFloat ^self x: aFloat y: aFloat z: aFloat! !!B3DVector3 class methodsFor: 'instance creation'!x: x y: y z: z ^self new x: x y: y z: z! !!B3DVector3 class methodsFor: 'instance creation'!zero ^self new! !!B3DVector3Array class methodsFor: 'instance creation' stamp: 'ar 2/5/1999 22:51'!contentsClass ^B3DVector3! !I represent 3D points in homogenous coordinates.!!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:16'!w ^self at: 4! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:17'!w: aFloat self at: 4 put: aFloat! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:16'!x ^self at: 1! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:17'!x: aFloat self at: 1 put: aFloat! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:16'!y ^self at: 2! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:17'!y: aFloat self at: 2 put: aFloat! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:16'!z ^self at: 3! !!B3DVector4 methodsFor: 'accessing' stamp: 'ar 2/1/1999 21:17'!z: aFloat self at: 3 put: aFloat! !!B3DVector4 methodsFor: 'private'!privateLoadFrom: srcObject self x: srcObject x y: srcObject y z: srcObject z w: srcObject w.! !!B3DVector4 methodsFor: 'initialize'!x: x y: y z: z w: w self x: x. self y: y. self z: z. self w: w.! !!B3DVector4 methodsFor: 'converting' stamp: 'ar 2/6/1999 00:08'!asB3DVector3 | wValue | wValue _ self w. wValue = 0.0 ifTrue:[^B3DVector3 zero]. ^B3DVector3 x: self x / wValue y: self y / wValue z: self z / wValue! !!B3DVector4 methodsFor: 'converting' stamp: 'ar 2/6/1999 00:07'!asB3DVector4 ^self! !!B3DVector4 class methodsFor: 'instance creation' stamp: 'ar 2/1/1999 21:21'!numElements ^4! !!B3DVector4 class methodsFor: 'instance creation'!x: x y: y z: z ^self x: x y: y z: z w: 1.0! !!B3DVector4 class methodsFor: 'instance creation'!x: x y: y z: z w: w ^self new x: x y: y z: z w: w! !!B3DVector4 class methodsFor: 'instance creation'!zero ^self new! !I represent the vertex buffer passed on throughout the entire Balloon 3D rendering pipeline. I store all information that may be needed by either part of the pipeline.Instance variables: current <B3DPrimitiveVertex> Tracking the current attributes of vertices vertexArray <B3DPrimitiveVertexArray> Container for all primitive vertices vertexCount <Integer> The number of vertices in the vertex array indexArray <WordArray> Stores the indexes for indexed primitives indexCount <Integer> Number of indexes in the index array primitive <Integer> The type of primitive currently in the buffer clipFlags <Integer> The clip mask of the vertices in the buffer flags <Integer> Various state flags !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/5/1999 18:44'!clipFlags ^clipFlags! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/5/1999 18:44'!clipFlags: aNumber clipFlags _ aNumber! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/8/1999 17:39'!flags ^flags! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/8/1999 17:40'!flags: newFlags "Note: should be used with CARE!!" flags _ newFlags! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/7/1999 02:13'!indexArray ^indexArray! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/7/1999 02:13'!indexArray: aWordArray indexArray _ aWordArray! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/7/1999 02:13'!indexCount ^indexCount! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/7/1999 02:14'!indexCount: aNumber indexCount _ aNumber! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/5/1999 18:48'!primitive ^primitive! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/5/1999 18:49'!primitive: aNumber primitive _ aNumber.! !!B3DVertexBuffer methodsFor: 'accessing'!vertexArray ^vertexArray! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/5/1999 18:44'!vertexArray: aB3DVertexArray vertexArray _ aB3DVertexArray! !!B3DVertexBuffer methodsFor: 'accessing'!vertexCount ^vertexCount! !!B3DVertexBuffer methodsFor: 'accessing' stamp: 'ar 2/5/1999 18:44'!vertexCount: aNumber vertexCount _ aNumber! !!B3DVertexBuffer methodsFor: 'initialize' stamp: 'ar 2/13/1999 20:24'!initialize vertexArray _ B3DPrimitiveVertexArray new: 100. vertexCount _ 0. indexArray _ WordArray new: 100. indexCount _ 0. current _ B3DPrimitiveVertex new. flags _ 0. primitive _ nil.! !!B3DVertexBuffer methodsFor: 'initialize' stamp: 'ar 2/13/1999 20:24'!reset vertexCount _ 0. indexCount _ 0.! !!B3DVertexBuffer methodsFor: 'attributes'!color ^current color! !!B3DVertexBuffer methodsFor: 'attributes'!color: aColor current color: aColor! !!B3DVertexBuffer methodsFor: 'attributes' stamp: 'ar 2/15/1999 00:09'!loadIndexed: idxArray vertices: vertices normals: normals colors: colors texCoords: texCoords | vtxSize idxSize maxVtx maxIdx | "Check the size of the vertex array" vtxSize _ vertices size. vertexCount + vtxSize >= vertexArray size ifTrue:[ self growVertexArray: (vtxSize + vertexArray size + 100). ]. "Check the size of the index array" idxSize _ idxArray basicSize. indexCount + idxSize >= indexArray size ifTrue:[ self growIndexArray: (idxSize + indexArray size + 100). ]. "Check the sizes of normals, colors, and texCoords" (normals notNil and:[vtxSize ~= normals size]) ifTrue:[^self errorSizeMismatch]. (colors notNil and:[vtxSize ~= colors size]) ifTrue:[^self errorSizeMismatch]. (texCoords notNil and:[vtxSize ~= texCoords size]) ifTrue:[^self errorSizeMismatch]. "Turn off the appropriate flags if no attributes are given. Default to having vertex normals and texture coords." flags _ flags bitOr: (VBVtxHasNormals + VBVtxHasTexCoords). "Turn off tracking flags if no colors are given" colors ifNil:[flags _ flags bitAnd: VBNoTrackMask]. normals ifNil:[flags _ flags bitAnd: VBVtxHasNormals bitInvert32]. texCoords ifNil:[flags _ flags bitAnd: VBVtxHasTexCoords bitInvert32]. "Load the vertices" maxVtx _ self primLoadVB: vertexArray startingAt: vertexCount vertices: vertices normals: normals colors: colors texCoords: texCoords count: vtxSize default: current. "Load the indexes" maxIdx _ self primLoadIndexArrayInto: indexArray startingAt: indexCount from: idxArray count: idxSize max: maxVtx offset: vertexCount. "Adjust the size of the vertex array and the index array" vertexCount _ vertexCount + maxVtx. indexCount _ indexCount + maxIdx.! !!B3DVertexBuffer methodsFor: 'attributes'!normal ^current normal! !!B3DVertexBuffer methodsFor: 'attributes'!normal: aVector current normal: aVector! !!B3DVertexBuffer methodsFor: 'attributes'!texCoords ^current texCoords! !!B3DVertexBuffer methodsFor: 'attributes'!texCoords: aVector current texCoords: aVector! !!B3DVertexBuffer methodsFor: 'attributes' stamp: 'ar 2/8/1999 17:37'!trackAmbientColor: aBool aBool ifTrue:[flags _ flags bitOr: VBTrackAmbient] ifFalse:[flags _ flags bitAnd: VBTrackAmbient bitInvert32]! !!B3DVertexBuffer methodsFor: 'attributes' stamp: 'ar 2/8/1999 17:37'!trackDiffuseColor: aBool aBool ifTrue:[flags _ flags bitOr: VBTrackDiffuse] ifFalse:[flags _ flags bitAnd: VBTrackDiffuse bitInvert32]! !!B3DVertexBuffer methodsFor: 'attributes' stamp: 'ar 2/8/1999 17:37'!trackEmissionColor: aBool aBool ifTrue:[flags _ flags bitOr: VBTrackEmission] ifFalse:[flags _ flags bitAnd: VBTrackEmission bitInvert32]! !!B3DVertexBuffer methodsFor: 'attributes' stamp: 'ar 2/8/1999 17:37'!trackSpecularColor: aBool aBool ifTrue:[flags _ flags bitOr: VBTrackSpecular] ifFalse:[flags _ flags bitAnd: VBTrackSpecular bitInvert32]! !!B3DVertexBuffer methodsFor: 'attributes'!vertex ^current position! !!B3DVertexBuffer methodsFor: 'attributes' stamp: 'ar 2/7/1999 04:05'!vertex: aVector current position: aVector. self addPrimitiveVertex: current.! !!B3DVertexBuffer methodsFor: 'private' stamp: 'ar 2/7/1999 02:31'!errorSizeMismatch ^self error:'Vertex size mismatch'! !!B3DVertexBuffer methodsFor: 'private' stamp: 'ar 2/7/1999 02:41'!growIndexArray: newSize | newIdxArray | newIdxArray _ indexArray species new: newSize. newIdxArray replaceFrom: 1 to: indexArray size with: indexArray startingAt: 1. indexArray _ newIdxArray.! !!B3DVertexBuffer methodsFor: 'private' stamp: 'ar 4/14/1999 02:35'!growVertexArray: newSize | newVtxArray | newVtxArray _ vertexArray species new: newSize. newVtxArray privateReplaceFrom: 1 to: vertexArray basicSize with: vertexArray startingAt: 1. vertexArray _ newVtxArray.! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:32'!hasVertexNormals ^flags anyMask: VBVtxHasNormals! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:32'!hasVertexTexCoords ^flags anyMask: VBVtxHasTexCoords! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:32'!trackAmbientColor "Return true if the vertex colors override the ambient part of material entries." ^flags anyMask: VBTrackAmbient! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:32'!trackDiffuseColor "Return true if the vertex colors override the diffuse part of material entries." ^flags anyMask: VBTrackDiffuse! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:32'!trackEmissionColor "Return true if the vertex colors override the emissive part of material entries." ^flags anyMask: VBTrackEmission! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:33'!trackSpecularColor "Return true if the vertex colors override the specular part of material entries." ^flags anyMask: VBTrackSpecular! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:35'!twoSidedLighting "Return true if we shade front and back facing polygons differently" ^flags anyMask: VBTwoSidedLighting! !!B3DVertexBuffer methodsFor: 'testing' stamp: 'ar 2/8/1999 17:35'!useLocalViewer ^flags anyMask: VBUseLocalViewer! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 4/19/1999 16:16'!addClipIndex: index "Add a primitive index to the list of indexes." indexCount >= indexArray size ifTrue:[self growIndexArray: indexCount + (indexCount // 4) + 10]. indexArray at: (indexCount _ indexCount + 1) put: index.! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 4/19/1999 16:16'!addClipVertex: pVtx "Add a primitive vertex to the list of vertices processed. Return the index of the vertex." vertexCount >= vertexArray size ifTrue:[self growVertexArray: vertexCount + (vertexCount // 4) + 10]. vertexArray at: (vertexCount _ vertexCount + 1) put: pVtx. ^vertexCount! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 23:13'!addPrimitiveIndex: index "Add a primitive index to the list of indexes." indexCount >= indexArray size ifTrue:[self growIndexArray: indexCount * 3 // 2 + 100]. indexArray at: (indexCount _ indexCount + 1) put: index.! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 04:02'!addPrimitiveVertex: pVtx "Add a primitive vertex to the list of vertices processed. Return the index of the vertex." vertexCount >= vertexArray size ifTrue:[self growVertexArray: vertexCount * 3 // 2 + 100]. vertexArray at: (vertexCount _ vertexCount + 1) put: pVtx. ^vertexCount! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 23:16'!growForClip vertexCount*2+100 > vertexArray size ifTrue:[self growVertexArray: vertexCount*2+100]. indexCount*2+100 > indexArray size ifTrue:[self growIndexArray: indexCount*2+100].! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 16:07'!primitiveColorAt: index ^(vertexArray at: index) color! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 04:04'!primitiveIndexAt: index ^indexArray at: index! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 04:05'!primitiveIndexAt: index put: value ^indexArray at: index put: value! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 04:04'!primitiveVertexAt: index ^vertexArray at: index! !!B3DVertexBuffer methodsFor: 'protected' stamp: 'ar 2/7/1999 04:04'!primitiveVertexAt: index put: aPrimitiveVertex ^vertexArray at: index put: aPrimitiveVertex! !!B3DVertexBuffer methodsFor: 'primitives' stamp: 'ar 4/5/1999 11:48'!primLoadIndexArrayInto: dstArray startingAt: dstStart from: idxArray count: count max: maxValue offset: vtxOffset "Primitive. Load the given index array into the receiver. NOTE: dstStart is a zero-based index." | idx | <primitive:'b3dLoadIndexArray' module:'Squeak3D'> "self flag: #b3dDebug. self primitiveFailed." 1 to: count do:[:i| idx _ idxArray basicAt: i. (idx < 1 or:[idx > maxValue]) ifTrue:[^self error:'Index out of range']. dstArray at: dstStart + i put: idx + vtxOffset. ]. ^count! !!B3DVertexBuffer methodsFor: 'primitives' stamp: 'ar 4/5/1999 11:48'!primLoadVB: dstArray startingAt: dstStart vertices: vertices normals: normals colors: colors texCoords: texCoords count: count default: defaultValues | hasNormals hasColors hasTexCoords pVtx defaultNormal defaultColor defaultTexCoords | <primitive:'b3dLoadVertexBuffer' module:'Squeak3D'> "self flag: #b3dDebug. self primitiveFailed." defaultNormal _ defaultValues normal. defaultColor _ defaultValues color. defaultTexCoords _ defaultValues texCoords. hasNormals _ normals notNil. hasColors _ colors notNil. hasTexCoords _ texCoords notNil. 1 to: count do:[:i| pVtx _ dstArray at: dstStart + i. pVtx position: (vertices at: i). pVtx normal: (hasNormals ifTrue:[normals at: i] ifFalse:[defaultNormal]). pVtx color: (hasColors ifTrue:[colors at: i] ifFalse:[defaultColor]). pVtx texCoords: (hasTexCoords ifTrue:[texCoords at: i] ifFalse:[defaultTexCoords]). dstArray at: dstStart + i put: pVtx. ]. ^count! !!B3DVertexBuffer class methodsFor: 'instance creation'!new ^super new initialize! !!B3DVertexBufferPlugin methodsFor: 'primitives' stamp: 'ar 2/14/1999 23:32'!b3dLoadIndexArray "Primitive. Load the given index array into the receiver. NOTE: dstStart is a zero-based index." | vtxOffset maxValue count srcArray srcPtr idx dstStart dstArray dstSize dstPtr | self export: true. self inline: false. self var: #dstPtr declareC:'int *dstPtr'. self var: #srcPtr declareC:'int *srcPtr'. "Load the arguments" vtxOffset _ interpreterProxy stackIntegerValue: 0. maxValue _ interpreterProxy stackIntegerValue: 1. count _ interpreterProxy stackIntegerValue: 2. srcArray _ interpreterProxy stackObjectValue: 3. dstStart _ interpreterProxy stackIntegerValue: 4. dstArray _ interpreterProxy stackObjectValue: 5. interpreterProxy failed ifTrue:[^nil]. "Will cover all possible problems above" "Check srcArray" (interpreterProxy isWords: srcArray) ifFalse:[^interpreterProxy primitiveFail]. ((interpreterProxy slotSizeOf: srcArray) < count) ifTrue:[^interpreterProxy primitiveFail]. srcPtr _ self cCoerce: (interpreterProxy firstIndexableField: srcArray) to:'int*'. "Check dstArray" dstSize _ interpreterProxy slotSizeOf: dstArray. "Check if there is enough room left in dstArray" dstStart + count > dstSize ifTrue:[^interpreterProxy primitiveFail]. dstPtr _ self cCoerce: (interpreterProxy firstIndexableField: dstArray) to:'int *'. "Do the actual work" 0 to: count-1 do:[:i| idx _ srcPtr at: i. (idx < 1 or:[idx > maxValue]) ifTrue:[^interpreterProxy primitiveFail]. dstPtr at: dstStart + i put: idx + vtxOffset. ]. "Clean up the stack" interpreterProxy pop: 7. "Pop args+rcvr" interpreterProxy pushInteger: count.! !!B3DVertexBufferPlugin methodsFor: 'primitives' stamp: 'ar 2/17/1999 04:30'!b3dLoadVertexBuffer "Primitive. Load the data into the given vertex buffer. NOTE: dstStart is a zero-based index." | defaultVtx defaultNormal defaultTexCoords defaultColor count texPtr colorPtr normalPtr vtxPtr dstStart dstPtr pVtx | self export: true. self inline: false. self var: #defaultVtx declareC:'int *defaultVtx'. self var: #defaultNormal declareC:'int *defaultNormal'. self var: #defaultTexCoords declareC:'int *defaultTexCoords'. self var: #defaultColor declareC:'int *defaultColor'. self var: #texPtr declareC:'int *texPtr'. self var: #colorPtr declareC:'int *colorPtr'. self var: #normalPtr declareC:'int *normalPtr'. self var: #vtxPtr declareC:'int *vtxPtr'. self var: #dstPtr declareC:'int *dstPtr'. self var: #pVtx declareC:'int *pVtx'. defaultVtx _ self stackPrimitiveVertex: 0. count _ interpreterProxy stackIntegerValue: 1. texPtr _ self vbLoadArray: (interpreterProxy stackObjectValue: 2) size: 2*count. colorPtr _ self vbLoadArray: (interpreterProxy stackObjectValue: 3) size: count. normalPtr _ self vbLoadArray: (interpreterProxy stackObjectValue: 4) size: 3*count. vtxPtr _ self vbLoadArray: (interpreterProxy stackObjectValue: 5) size: 3*count. dstStart _ interpreterProxy stackIntegerValue: 6. dstPtr _ self stackPrimitiveVertexArray: 7 ofSize: dstStart + count. "Check for all problems above" (dstPtr = nil or:[defaultVtx == nil or:[interpreterProxy failed]]) ifTrue:[^interpreterProxy primitiveFail]. "Install default values" normalPtr = nil ifTrue:[defaultNormal _ defaultVtx + PrimVtxNormal] ifFalse:[defaultNormal _ normalPtr]. texPtr = nil ifTrue:[defaultTexCoords _ defaultVtx + PrimVtxTexCoords] ifFalse:[defaultTexCoords _ texPtr]. colorPtr = nil ifTrue:[defaultColor _ defaultVtx + PrimVtxColor32] ifFalse:[defaultColor _ colorPtr]. "Do the actual stuff" pVtx _ dstPtr + (dstStart * PrimVertexSize). 0 to: count-1 do:[:i| pVtx at: PrimVtxPositionX put: (vtxPtr at: 0). pVtx at: PrimVtxPositionY put: (vtxPtr at: 1). pVtx at: PrimVtxPositionZ put: (vtxPtr at: 2). pVtx at: PrimVtxNormalX put: (defaultNormal at: 0). pVtx at: PrimVtxNormalY put: (defaultNormal at: 1). pVtx at: PrimVtxNormalZ put: (defaultNormal at: 2). pVtx at: PrimVtxColor32 put: (defaultColor at: 0). pVtx at: PrimVtxTexCoordU put: (defaultTexCoords at: 0). pVtx at: PrimVtxTexCoordV put: (defaultTexCoords at: 1). "And go to the next vertex" pVtx _ pVtx + PrimVertexSize. vtxPtr _ vtxPtr + 3. normalPtr = nil ifFalse:[defaultNormal _ defaultNormal + 3]. colorPtr = nil ifFalse:[defaultColor _ defaultColor + 1]. texPtr = nil ifFalse:[defaultTexCoords _ defaultTexCoords + 2]. ]. "Clean up stack" interpreterProxy pop: 8. "Pop args+rcvr" interpreterProxy pushInteger: count.! !!B3DVertexBufferPlugin methodsFor: 'private' stamp: 'ar 4/17/1999 22:29'!vbLoadArray: oop size: count "Load the word based array of size count from the given oop" self returnTypeC: 'void*'. self inline: false. oop == nil ifTrue:[interpreterProxy primitiveFail. ^nil]. oop == interpreterProxy nilObject ifTrue:[^nil]. (interpreterProxy isWords: oop) ifFalse:[interpreterProxy primitiveFail. ^nil]. (interpreterProxy slotSizeOf: oop) = count ifFalse:[interpreterProxy primitiveFail. ^nil]. ^interpreterProxy firstIndexableField: oop! !I provide clipping capabilities for rasterizers needing explicit clipping.!!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 4/17/1999 23:06'!processIndexedLines: vb "Process an indexed line set" ^self error:'Lines are not yet implemented'! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 9/17/1999 20:08'!processIndexedQuads: vb "Clip an indexed quad set" | vtxArray idxArray tempVB idx1 idx2 idx3 maxVtx maxIdx index lastIndex clipFlags vtx returnValue | self flag: #b3dPrimitive. returnValue _ false. "Assume we don't see nothing" tempVB _ B3DVertexBuffer new. vtxArray _ vb vertexArray. idxArray _ vb indexArray. maxVtx _ vb indexCount. maxIdx _ vb indexCount. lastIndex _ -3. "Hack the lastIndex ;-)" [index _ self primNextClippedQuadAfter: lastIndex + 4 vertices: vtxArray count: maxVtx indexes: idxArray count: maxIdx. index = 0] whileFalse:[ "Need a partial clip here, storing the triangulated polygon at the end" tempVB reset. clipFlags _ InAllMask + OutAllMask. "Copy the poly into tempVB" 0 to: 3 do:[:i| vtx _ vtxArray at: (idxArray at: index+i). idxArray at: index+i put: 0. tempVB addClipVertex: vtx. clipFlags _ clipFlags bitAnd: vtx clipFlags]. tempVB clipFlags: clipFlags. self processPolygon: tempVB. tempVB vertexCount > 2 ifTrue:[ returnValue _ nil. "We see some parts and not others" idx1 _ vb addClipVertex: (tempVB vertexArray at: 1). 3 to: tempVB vertexCount do:[:j| idx2 _ vb addClipVertex: (tempVB vertexArray at: j-1). idx3 _ vb addClipVertex: (tempVB vertexArray at: j). vb addClipIndex: idx1. vb addClipIndex: idx2. vb addClipIndex: idx3. vb addClipIndex: idx3. ]. ]. lastIndex _ index. ]. ^returnValue! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 9/17/1999 20:08'!processIndexedTriangles: vb "Clip an indexed triangle set" | vtxArray idxArray tempVB idx1 idx2 idx3 maxVtx maxIdx index lastIndex clipFlags vtx returnValue | self flag: #b3dPrimitive. returnValue _ false. "Assume we don't see nothing" tempVB _ B3DVertexBuffer new. vtxArray _ vb vertexArray. idxArray _ vb indexArray. maxVtx _ vb indexCount. maxIdx _ vb indexCount. lastIndex _ -2. "Hack the lastIndex ;-)" [index _ self primNextClippedTriangleAfter: lastIndex + 3 vertices: vtxArray count: maxVtx indexes: idxArray count: maxIdx. index = 0] whileFalse:[ "Need a partial clip here, storing the triangulated polygon at the end" tempVB reset. clipFlags _ InAllMask + OutAllMask. "Copy the poly into tempVB" 0 to: 2 do:[:i| vtx _ vtxArray at: (idxArray at: index+i). idxArray at: index+i put: 0. tempVB addClipVertex: vtx. clipFlags _ clipFlags bitAnd: vtx clipFlags]. tempVB clipFlags: clipFlags. self processPolygon: tempVB. tempVB vertexCount > 2 ifTrue:[ returnValue _ nil. "We see some parts and not others" idx1 _ vb addClipVertex: (tempVB vertexArray at: 1). 3 to: tempVB vertexCount do:[:j| idx2 _ vb addClipVertex: (tempVB vertexArray at: j-1). idx3 _ vb addClipVertex: (tempVB vertexArray at: j). vb addClipIndex: idx1. vb addClipIndex: idx2. vb addClipIndex: idx3. ]. ]. lastIndex _ index. ]. ^returnValue! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 4/17/1999 23:06'!processLineLoop: vertexBuffer "Process a closed line defined by the vertex buffer" ^self error:'Lines are not yet implemented'! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 4/17/1999 23:06'!processLines: vertexBuffer "Process a series of lines defined by each two points the vertex buffer" ^self error:'Lines are not yet implemented'! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 4/17/1999 23:06'!processPoints: vertexBuffer "Process a series of points defined by the vertex buffer" ^self error:'Points are not yet implemented'! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 9/17/1999 20:10'!processPolygon: vb "Process a polygon from the vertex buffer that requires partial clipping" | outMask vtxArray tempVtxArray count | outMask := vb clipFlags bitAnd: OutAllMask. vtxArray _ vb vertexArray. tempVtxArray _ vtxArray clone. "Note: tempVtxArray has the SAME contents as vtxArray since the data is stored inplace. Thus we can decide from which buffer to start the clipping operation later on." count _ self clipPolygon: vtxArray count: vb vertexCount with: tempVtxArray mask: outMask. vb vertexCount: count. count < 3 ifTrue:[^false]. ^nil! !!B3DVertexClipper methodsFor: 'processing' stamp: 'ar 9/17/1999 20:05'!processVertexBuffer: vb "Clip the elements in the vertex buffer. Return true if all vertices are inside. Return false if all vertices are outside. If partial clipping occurs, return nil." | fullMask | fullMask _ self determineClipFlags: vb vertexArray count: vb vertexCount. vb clipFlags: fullMask. "Check if all vertices are inside, so no clipping is necessary" (fullMask allMask: InAllMask) ifTrue:[^true]. "Check if all vertices are outside, so we can get rid of the entire buffer" (fullMask anyMask: OutAllMask) ifTrue:[ "Reset the number of vertices in the vertex buffer to zero to indicate all outside" vb reset. ^false]. "Must clip individual items depending on the primitive type" vb growForClip. "Make sure we have enough space during primitive operation" ^super processVertexBuffer: vb.! !!B3DVertexClipper methodsFor: 'clip flags' stamp: 'ar 2/16/1999 19:20'!clipFlagsX: x y: y z: z w: w "Determine the clip flags for the given vector. The clip flags are a combination of inside and outside flags that can be used to easily reject an entire buffer if it is completely inside or outside and can also be used to detect the most commen cases in clipping (e.g., intersection with one boundary only)." | w2 flags | w2 _ w negated. flags _ 0. flags _ flags bitOr:(x >= w2 ifTrue:[InLeftBit] ifFalse:[OutLeftBit]). flags _ flags bitOr:(x <= w ifTrue:[InRightBit] ifFalse:[OutRightBit]). flags _ flags bitOr:(y >= w2 ifTrue:[InBottomBit] ifFalse:[OutBottomBit]). flags _ flags bitOr:(y <= w ifTrue:[InTopBit] ifFalse:[OutTopBit]). flags _ flags bitOr:(z >= w2 ifTrue:[InFrontBit] ifFalse:[OutFrontBit]). flags _ flags bitOr:(z <= w ifTrue:[InBackBit] ifFalse:[OutBackBit]). ^flags! !!B3DVertexClipper methodsFor: 'clip flags' stamp: 'ar 2/16/1999 19:20'!determineClipFlags: vtxArray count: vtxCount "Determine the clip flags for all the vertices in the vertex array" | fullMask flags | self flag: #b3dPrimitive. fullMask _ InAllMask + OutAllMask. vtxArray upTo: vtxCount do:[:vtx| flags _ (self clipFlagsX: vtx rasterPosX y: vtx rasterPosY z: vtx rasterPosZ w: vtx rasterPosW). vtx clipFlags: flags. fullMask _ fullMask bitAnd: flags. ]. ^fullMask! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 2/16/1999 19:21'!clipPolygon: vtxArray count: vtxCount with: tempVtxArray mask: outMask "Clip the polygon defined by vtxCount vertices in vtxArray. tempVtxArray is a temporary storage area used for copying the vertices back and forth during clipping operation. outMask is the full clip mask of the vertex buffer, allowing some optimizations of the clipping code. NOTE: It is significant here that the contents of vtxArray and tempVtxArray are equal." | count | self flag: #b3dPrimitive. "Check if the polygon is outside one boundary only. If so, just do this single clipping operation avoiding multiple enumeration." outMask = OutLeftBit ifTrue:[^self clipPolygonLeftFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutRightBit ifTrue:[^self clipPolygonRightFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutTopBit ifTrue:[^self clipPolygonTopFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutBottomBit ifTrue:[^self clipPolygonBottomFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutFrontBit ifTrue:[^self clipPolygonFrontFrom: tempVtxArray to: vtxArray count: vtxCount]. outMask = OutBackBit ifTrue:[^self clipPolygonBackFrom: tempVtxArray to: vtxArray count: vtxCount]. "Just do each of the clipping operations" count _ vtxCount. count _ self clipPolygonLeftFrom: vtxArray to: tempVtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonRightFrom: tempVtxArray to: vtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonTopFrom: vtxArray to: tempVtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonBottomFrom: tempVtxArray to: vtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonFrontFrom: vtxArray to: tempVtxArray count: count. count = 0 ifTrue:[^0]. count _ self clipPolygonBackFrom: tempVtxArray to: vtxArray count: count. ^count! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 2/16/1999 19:21'!clipPolygonBackFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext outVtx | outIndex _ 0. last _ buf1 at: n. inLast _ last clipFlags anyMask: InBackBit. 1 to: n do:[:i| next _ buf1 at: i. inNext _ next clipFlags anyMask: InBackBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self backClipValueFrom: last to: next. outVtx _ self interpolateFrom: last to: next at: t. buf2 at: (outIndex _ outIndex+1) put: outVtx]. inNext ifTrue:[buf2 at: (outIndex _ outIndex+1) put: next]. last _ next. inLast _ inNext. ]. ^outIndex! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 2/16/1999 19:21'!clipPolygonBottomFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext outVtx | outIndex _ 0. last _ buf1 at: n. inLast _ last clipFlags anyMask: InBottomBit. 1 to: n do:[:i| next _ buf1 at: i. inNext _ next clipFlags anyMask: InBottomBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self bottomClipValueFrom: last to: next. outVtx _ self interpolateFrom: last to: next at: t. buf2 at: (outIndex _ outIndex+1) put: outVtx]. inNext ifTrue:[buf2 at: (outIndex _ outIndex+1) put: next]. last _ next. inLast _ inNext. ]. ^outIndex! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 2/16/1999 19:21'!clipPolygonFrontFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext outVtx | outIndex _ 0. last _ buf1 at: n. inLast _ last clipFlags anyMask: InFrontBit. 1 to: n do:[:i| next _ buf1 at: i. inNext _ next clipFlags anyMask: InFrontBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self frontClipValueFrom: last to: next. outVtx _ self interpolateFrom: last to: next at: t. buf2 at: (outIndex _ outIndex+1) put: outVtx]. inNext ifTrue:[buf2 at: (outIndex _ outIndex+1) put: next]. last _ next. inLast _ inNext. ]. ^outIndex! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 4/16/1999 06:01'!clipPolygonLeftFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext outVtx | outIndex _ 0. last _ buf1 at: n. inLast _ last clipFlags anyMask: InLeftBit. 1 to: n do:[:i| next _ buf1 at: i. inNext _ next clipFlags anyMask: InLeftBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self leftClipValueFrom: last to: next. outVtx _ self interpolateFrom: last to: next at: t. buf2 at: (outIndex _ outIndex+1) put: outVtx]. inNext ifTrue:[buf2 at: (outIndex _ outIndex+1) put: next]. last _ next. inLast _ inNext. ]. ^outIndex! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 2/16/1999 19:21'!clipPolygonRightFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext outVtx | outIndex _ 0. last _ buf1 at: n. inLast _ last clipFlags anyMask: InRightBit. 1 to: n do:[:i| next _ buf1 at: i. inNext _ next clipFlags anyMask: InRightBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self rightClipValueFrom: last to: next. outVtx _ self interpolateFrom: last to: next at: t. buf2 at: (outIndex _ outIndex+1) put: outVtx]. inNext ifTrue:[buf2 at: (outIndex _ outIndex+1) put: next]. last _ next. inLast _ inNext. ]. ^outIndex! !!B3DVertexClipper methodsFor: 'clipping polygons' stamp: 'ar 2/16/1999 19:21'!clipPolygonTopFrom: buf1 to: buf2 count: n | last next t outIndex inLast inNext outVtx | outIndex _ 0. last _ buf1 at: n. inLast _ last clipFlags anyMask: InTopBit. 1 to: n do:[:i| next _ buf1 at: i. inNext _ next clipFlags anyMask: InTopBit. inLast = inNext ifFalse:["Passes clip boundary" t _ self topClipValueFrom: last to: next. outVtx _ self interpolateFrom: last to: next at: t. buf2 at: (outIndex _ outIndex+1) put: outVtx]. inNext ifTrue:[buf2 at: (outIndex _ outIndex+1) put: next]. last _ next. inLast _ inNext. ]. ^outIndex! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 2/16/1999 19:21'!backClipValueFrom: last to: next ^(last rasterPosZ - last rasterPosW) / ((next rasterPosW - last rasterPosW) - (next rasterPosZ - last rasterPosZ)).! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 2/16/1999 19:21'!bottomClipValueFrom: last to: next ^(last rasterPosY + last rasterPosW) negated / ((next rasterPosW - last rasterPosW) + (next rasterPosY - last rasterPosY)).! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 2/16/1999 19:21'!frontClipValueFrom: last to: next ^(last rasterPosZ + last rasterPosW) negated / ((next rasterPosW - last rasterPosW) + (next rasterPosZ - last rasterPosZ)).! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 4/16/1999 06:43'!interpolateFrom: last to: next at: t "Interpolate the primitive vertices last/next at the parameter t" | out | out _ next clone. "Interpolate raster position" out rasterPos: ((next rasterPos - last rasterPos) * t) + last rasterPos. out clipFlags: (self clipFlagsX: out rasterPosX y: out rasterPosY z: out rasterPosZ w: out rasterPosW). "Interpolate color" out b3dColor: ((next b3dColor - last b3dColor) * t) + last b3dColor. "Interpolate texture coordinates" out texCoords: ((next texCoords - last texCoords) * t) + last texCoords. ^out! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 2/16/1999 19:21'!leftClipValueFrom: last to: next ^(last rasterPosX + last rasterPosW) negated / ((next rasterPosW - last rasterPosW) + (next rasterPosX - last rasterPosX)).! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 2/16/1999 19:21'!rightClipValueFrom: last to: next ^(last rasterPosX - last rasterPosW) / ((next rasterPosW - last rasterPosW) - (next rasterPosX - last rasterPosX)).! !!B3DVertexClipper methodsFor: 'clipping utilitites' stamp: 'ar 2/16/1999 19:21'!topClipValueFrom: last to: next ^(last rasterPosY - last rasterPosW) / ((next rasterPosW - last rasterPosW) - (next rasterPosY - last rasterPosY)).! !!B3DVertexClipper methodsFor: 'private' stamp: 'ar 2/16/1999 19:21'!primNextClippedQuadAfter: firstIndex vertices: vtxArray count: vtxCount indexes: idxArray count: idxCount "Find the next partially clipped quad from the vertex buffer and return its index. If there are no more partially clipped quads return zero." | quadMask | self flag: #b3dPrimitive. firstIndex to: idxCount by: 4 do:[:i| quadMask _ ((vtxArray at: (idxArray at: i)) clipFlags bitAnd: (vtxArray at: (idxArray at: i+1)) clipFlags) bitAnd: ((vtxArray at: (idxArray at: i+2)) clipFlags bitAnd: (vtxArray at: (idxArray at: i+3)) clipFlags). "Check if quad is completely inside" (quadMask allMask: InAllMask) ifFalse:[ "Quad is not completely inside -> needs clipping." (quadMask anyMask: OutAllMask) ifTrue:[ "quad is completely outside. Store all zeros" idxArray at: i put: 0. idxArray at: i+1 put: 0. idxArray at: i+2 put: 0. idxArray at: i+3 put: 0. ] ifFalse:[ "quad must be partially clipped." ^i ]. ]. ]. ^0 "No more entries"! !!B3DVertexClipper methodsFor: 'private' stamp: 'ar 2/16/1999 19:22'!primNextClippedTriangleAfter: firstIndex vertices: vtxArray count: vtxCount indexes: idxArray count: idxCount "Find the next partially clipped triangle from the vertex buffer and return its index. If there are no more partially clipped triangles return zero." | triMask | self flag: #b3dPrimitive. firstIndex to: idxCount by: 3 do:[:i| triMask _ ((vtxArray at: (idxArray at: i)) clipFlags bitAnd: (vtxArray at: (idxArray at: i+1)) clipFlags) bitAnd: (vtxArray at: (idxArray at: i+2)) clipFlags. "Check if tri is completely inside" (triMask allMask: InAllMask) ifFalse:[ "Tri is not completely inside -> needs clipping." (triMask anyMask: OutAllMask) ifTrue:[ "tri is completely outside. Store all zeros" idxArray at: i put: 0. idxArray at: i+1 put: 0. idxArray at: i+2 put: 0. ] ifFalse:[ "tri must be partially clipped." ^i ]. ]. ]. ^0 "No more entries"! !!B3DVertexClipper class methodsFor: 'class initialization' stamp: 'ar 2/13/1999 20:31'!initialize "B3DClipper initialize" "InLeftBit _ 16r01. OutLeftBit _ 16r02. InRightBit _ 16r04. OutRightBit _ 16r08. InTopBit _ 16r10. OutTopBit _ 16r20. InBottomBit _ 16r40. OutBottomBit _ 16r80. InFrontBit _ 16r100. OutFrontBit _ 16r200. InBackBit _ 16r400. OutBackBit _ 16r800. InAllMask _ 16r555. 1365 OutAllMask _ 16rAAA 2730."! !!B3DVertexClipper class methodsFor: 'testing' stamp: 'ar 2/14/1999 01:40'!isAvailable "Return true if this part of the engine is available" ^true! !I am the superclass for all rasterizers in the Balloon 3D engine. Rasterizers perform the final pixel generation of the primitives and are the most time-critical part of the engine. Rasterizers keep a viewport, defining the destination rectangle and a dirtyRect, defining the actual affected 2D region of the rasterization process.Instance variables: viewport <B3DViewport> the destination rectangle dirtyRect <Rectangle> the affected region of all rasterization operations performed!!B3DVertexRasterizer methodsFor: 'initialize' stamp: 'ar 2/16/1999 04:30'!finish "Force everything on the output device"! !!B3DVertexRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:29'!flush "Flush pending operations."! !!B3DVertexRasterizer methodsFor: 'initialize' stamp: 'ar 2/16/1999 03:15'!initialize super initialize. textureStack _ OrderedCollection new.! !!B3DVertexRasterizer methodsFor: 'initialize' stamp: 'ar 4/10/1999 22:53'!reset super reset. textureStack _ OrderedCollection new.! !!B3DVertexRasterizer methodsFor: 'initialize' stamp: 'ar 5/26/2000 15:12'!target: aForm "Set the target for rendering operations" target _ aForm! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 5/26/2000 15:18'!clipRect "Return the current clipping rectangle" ^clipRect! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 5/26/2000 15:18'!clipRect: aRectangle "Install a clipping rectangle if necessary" clipRect _ aRectangle! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 2/7/1999 03:38'!dirtyRect "If the dirtyRect is not known (e.g., not implemented by a particular rasterizer) return the full viewport" ^dirtyRect ifNil:[viewport]! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 2/7/1999 03:35'!dirtyRect: aRectangle dirtyRect _ aRectangle! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:16'!popTexture texture _ textureStack removeLast.! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:15'!pushTexture textureStack addLast: texture! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:15'!texture ^texture! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 2/16/1999 03:15'!texture: aForm texture _ aForm! !!B3DVertexRasterizer methodsFor: 'accessing'!viewport ^viewport! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 5/26/2000 15:30'!viewport: aRectangle | r | r _ aRectangle. offset ifNotNil:[r _ r translateBy: offset]. viewport _ B3DViewport origin: r origin corner: r corner. viewport toggleYScale.! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 5/26/2000 15:17'!viewportOffset "Return the viewport offset" ^offset! !!B3DVertexRasterizer methodsFor: 'accessing' stamp: 'ar 5/26/2000 15:17'!viewportOffset: aPoint "Set the viewport offset" offset _ aPoint! !!B3DVertexRasterizer methodsFor: 'testing'!needsClip "Return true if we need to clip polygons before rasterization. Generally, this should not be the case." ^self subclassResponsibility! !!B3DVertexRasterizer methodsFor: 'processing' stamp: 'ar 2/16/1999 02:02'!clearDepthBuffer "If the rasterizer uses a depth buffer, clear it."! !!B3DVertexRasterizer methodsFor: 'processing' stamp: 'ar 5/28/2000 02:25'!clearViewport: aColor "Clear the current viewport using the given color" target ifNotNil:[ target fill: viewport rule: Form over fillColor: aColor asColor ].! !!B3DVertexRasterizer methodsFor: 'processing' stamp: 'ar 11/7/1999 18:04'!processVertexBuffer: vb vbBounds _ nil. super processVertexBuffer: vb. ^vbBounds! !!B3DVertexShader methodsFor: 'initialize' stamp: 'ar 2/17/1999 04:17'!initialize super initialize. lights _ OrderedCollection new. material _ B3DMaterial new. materialStack _ OrderedCollection new: 10.! !!B3DVertexShader methodsFor: 'initialize' stamp: 'ar 4/10/1999 22:55'!reset super reset. lights _ OrderedCollection new. material _ B3DMaterial new. materialStack _ OrderedCollection new: 10.! !!B3DVertexShader methodsFor: 'shading' stamp: 'ar 4/3/1999 20:10'!processVertexBuffer: vb | colors emissionPart | colors _ B3DColor4Array new: vb vertexCount. "Load initial colors (e.g., emission part)" vb trackEmissionColor ifFalse:[ emissionPart _ material emission. 1 to: vb vertexCount do:[:i| colors at: i put: emissionPart]. ] ifTrue:[ 1 to: vb vertexCount do:[:i| colors at: i put: (vb primitiveVertexAt: i) b3dColor]. ]. lights do:[:light| light shadeVertexBuffer: vb with: material into: colors. ]. colors clampAllFrom: 0.0 to: 1.0. vb vertexArray upTo: vb vertexCount doWithIndex:[:vtx :i| vtx color: (colors at: i)].! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:14'!addLight: aLightSource lights add: aLightSource. ^lights size! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:36'!material ^material! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:36'!material: aMaterial material _ aMaterial.! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/7/1999 16:19'!materialColor: aColor material ambientPart: aColor. material diffusePart: aColor. material specularPart: aColor.! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:35'!popMaterial material _ materialStack removeLast.! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/7/1999 19:35'!pushMaterial materialStack addLast: material.! !!B3DVertexShader methodsFor: 'accessing' stamp: 'ar 2/17/1999 04:16'!removeLight: lightIndex "Remove the light with the given index" (lightIndex < 1 or:[lightIndex > lights size]) ifTrue:[^nil]. lights at: lightIndex put: nil. "So we don't change the indexes"! !!B3DVertexShader class methodsFor: 'testing' stamp: 'ar 2/14/1999 01:41'!isAvailable "Return true if this part of the engine is available" ^true! !!B3DVertexTransformer methodsFor: 'initialize' stamp: 'ar 4/18/1999 02:23'!initialize super initialize. modelMatrix _ B3DMatrix4x4 identity. viewMatrix _ B3DMatrix4x4 identity. textureMatrix _ B3DMatrix4x4 identity. currentMatrix _ modelMatrix. matrixStack _ OrderedCollection new: 30. matrixStack resetTo: 1. needsUpdate _ false.! !!B3DVertexTransformer methodsFor: 'initialize' stamp: 'ar 4/16/1999 07:59'!reset super reset. modelMatrix := B3DMatrix4x4 identity. viewMatrix := B3DMatrix4x4 identity. textureMatrix := B3DMatrix4x4 identity. currentMatrix := modelMatrix. matrixStack := OrderedCollection new: 30. matrixStack resetTo: 1. needsUpdate := false.! !!B3DVertexTransformer methodsFor: 'public' stamp: 'ar 8/19/1999 16:31'!transformDirection: aVector3 | zero one | zero _ B3DVector3 new. one _ zero + aVector3. zero _ self transformPosition: zero. one _ self transformPosition: one. ^one - zero! !!B3DVertexTransformer methodsFor: 'public' stamp: 'ar 2/8/1999 01:33'!transformPosition: aVector3 | pVtx | pVtx _ B3DPrimitiveVertex new. pVtx position: aVector3. self privateTransformPrimitiveVertex: pVtx byModelView: self modelViewMatrix. ^pVtx position! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:58'!currentMatrix ^currentMatrix! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:58'!matrixMode currentMatrix == modelMatrix ifTrue:[^#modelView]. currentMatrix == viewMatrix ifTrue:[^#projection]. currentMatrix == textureMatrix ifTrue:[^#texture]. self error:'Bad matrix state'.! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:58'!matrixMode: aSymbol aSymbol == #modelView ifTrue:[currentMatrix := modelMatrix. ^self]. aSymbol == #projection ifTrue:[currentMatrix := viewMatrix. ^self]. aSymbol == #texture ifTrue:[currentMatrix := textureMatrix. ^self]. self error:'Bad matrix mode'.! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:58'!modelViewMatrix ^modelMatrix! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:59'!popMatrix "Pop the current matrix from the stack" matrixStack isEmpty ifTrue:[^self error:'Empty matrix stack']. currentMatrix loadFrom: matrixStack removeLast.! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:59'!projectionMatrix ^viewMatrix! !!B3DVertexTransformer methodsFor: 'accessing' stamp: 'ar 2/2/1999 18:59'!pushMatrix "Push the current matrix" | theMatrix | theMatrix := B3DMatrix4x4 new. theMatrix loadFrom: currentMatrix. matrixStack addLast: theMatrix.! !!B3DVertexTransformer methodsFor: 'modifying' stamp: 'ar 2/2/1999 19:00'!loadIdentity currentMatrix setIdentity. needsUpdate := true.! !!B3DVertexTransformer methodsFor: 'modifying' stamp: 'ar 2/2/1999 19:00'!loadMatrix: aMatrix currentMatrix loadFrom: aMatrix. needsUpdate := true.! !!B3DVertexTransformer methodsFor: 'modifying' stamp: 'ar 2/7/1999 01:39'!lookFrom: position to: target up: upDirection "create a matrix such that we look from eyePoint to centerPoint using upDirection" | xDir yDir zDir m | "calculate z vector" zDir _ target - position. zDir safelyNormalize. "calculate x vector" xDir _ upDirection cross: zDir. xDir safelyNormalize. "recalc y vector" yDir _ zDir cross: xDir. yDir safelyNormalize. m := B3DMatrix4x4 new. m a11: xDir x; a12: xDir y; a13: xDir z; a14: 0.0; a21: yDir x; a22: yDir y; a23: yDir z; a24: 0.0; a31: zDir x; a32: zDir y; a33: zDir z; a34: 0.0; a41: 0.0; a42: 0.0; a43: 0.0; a44: 1.0. self transformBy: m. self translateBy: position negated.! !!B3DVertexTransformer methodsFor: 'modifying' stamp: 'ar 2/2/1999 19:00'!multiplyMatrix: aMatrix "Multiply aMatrix with the current matrix" currentMatrix *= aMatrix! !!B3DVertexTransformer methodsFor: 'modifying'!rotateBy: aRotation self transformBy: aRotation asMatrix4x4.! !!B3DVertexTransformer methodsFor: 'modifying'!scaleBy: aVector self transformBy: (B3DMatrix4x4 identity setScale: aVector)! !!B3DVertexTransformer methodsFor: 'modifying' stamp: 'ar 2/2/1999 19:01'!scaleByX: x y: y z: z currentMatrix scaleByX: x y: y z: z. needsUpdate := true.! !!B3DVertexTransformer methodsFor: 'modifying'!transformBy: aTransformation self privateTransformMatrix: currentMatrix with: aTransformation asMatrix4x4 into: currentMatrix. needsUpdate := true.! !!B3DVertexTransformer methodsFor: 'modifying'!translateBy: aVector "Add the translation defined by aVector to the current matrix" self transformBy: (B3DMatrix4x4 identity setTranslation: aVector).! !!B3DVertexTransformer methodsFor: 'modifying' stamp: 'ar 2/2/1999 19:01'!translateByX: x y: y z: z "Add the translation defined by aVector to the current matrix" currentMatrix translateByX: x y: y z: z. needsUpdate := true.! !!B3DVertexTransformer methodsFor: 'processing' stamp: 'ar 4/18/1999 02:23'!processVertexBuffer: vb ^self processVertexBuffer: vb modelView: self modelViewMatrix projection: self projectionMatrix! !!B3DVertexTransformer methodsFor: 'processing' stamp: 'ar 4/18/1999 02:22'!processVertexBuffer: vb modelView: modelViewMatrix projection: projectionMatrix ^self privateTransformVB: vb vertexArray count: vb vertexCount modelViewMatrix: modelViewMatrix projectionMatrix: projectionMatrix flags: vb flags! !!B3DVertexTransformer methodsFor: 'view transformation'!ortho: aFrustum viewMatrix _ aFrustum asFrustum asOrthoMatrix. needsUpdate _ true.! !!B3DVertexTransformer methodsFor: 'view transformation'!perspective: aPerspectiveOrFrustum viewMatrix _ aPerspectiveOrFrustum asFrustum asPerspectiveMatrix. needsUpdate _ true.! !!B3DVertexTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:19'!privateTransformMatrix: m1 with: m2 into: m3 "Perform a 4x4 matrix multiplication m2 * m1 = m3 being equal to first transforming points by m2 and then by m1. Note that m1 may be identical to m3." | c1 c2 c3 c4 | m2 == m3 ifTrue:[^self error:'Argument and result matrix identical']. c1 _ ((m1 a11 * m2 a11) + (m1 a12 * m2 a21) + (m1 a13 * m2 a31) + (m1 a14 * m2 a41)). c2 _ ((m1 a11 * m2 a12) + (m1 a12 * m2 a22) + (m1 a13 * m2 a32) + (m1 a14 * m2 a42)). c3 _ ((m1 a11 * m2 a13) + (m1 a12 * m2 a23) + (m1 a13 * m2 a33) + (m1 a14 * m2 a43)). c4 _ ((m1 a11 * m2 a14) + (m1 a12 * m2 a24) + (m1 a13 * m2 a34) + (m1 a14 * m2 a44)). m3 a11: c1; a12: c2; a13: c3; a14: c4. c1 _ ((m1 a21 * m2 a11) + (m1 a22 * m2 a21) + (m1 a23 * m2 a31) + (m1 a24 * m2 a41)). c2 _ ((m1 a21 * m2 a12) + (m1 a22 * m2 a22) + (m1 a23 * m2 a32) + (m1 a24 * m2 a42)). c3 _ ((m1 a21 * m2 a13) + (m1 a22 * m2 a23) + (m1 a23 * m2 a33) + (m1 a24 * m2 a43)). c4 _ ((m1 a21 * m2 a14) + (m1 a22 * m2 a24) + (m1 a23 * m2 a34) + (m1 a24 * m2 a44)). m3 a21: c1; a22: c2; a23: c3; a24: c4. c1 _ ((m1 a31 * m2 a11) + (m1 a32 * m2 a21) + (m1 a33 * m2 a31) + (m1 a34 * m2 a41)). c2 _ ((m1 a31 * m2 a12) + (m1 a32 * m2 a22) + (m1 a33 * m2 a32) + (m1 a34 * m2 a42)). c3 _ ((m1 a31 * m2 a13) + (m1 a32 * m2 a23) + (m1 a33 * m2 a33) + (m1 a34 * m2 a43)). c4 _ ((m1 a31 * m2 a14) + (m1 a32 * m2 a24) + (m1 a33 * m2 a34) + (m1 a34 * m2 a44)). m3 a31: c1; a32: c2; a33: c3; a34: c4. c1 _ ((m1 a41 * m2 a11) + (m1 a42 * m2 a21) + (m1 a43 * m2 a31) + (m1 a44 * m2 a41)). c2 _ ((m1 a41 * m2 a12) + (m1 a42 * m2 a22) + (m1 a43 * m2 a32) + (m1 a44 * m2 a42)). c3 _ ((m1 a41 * m2 a13) + (m1 a42 * m2 a23) + (m1 a43 * m2 a33) + (m1 a44 * m2 a43)). c4 _ ((m1 a41 * m2 a14) + (m1 a42 * m2 a24) + (m1 a43 * m2 a34) + (m1 a44 * m2 a44)). m3 a41: c1; a42: c2; a43: c3; a44: c4.! !!B3DVertexTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:20'!privateTransformPrimitiveNormal: primitiveVertex byMatrix: aMatrix rescale: scaleNeeded | x y z rx ry rz dot | x _ primitiveVertex normalX. y _ primitiveVertex normalY. z _ primitiveVertex normalZ. rx := (x * aMatrix a11) + (y * aMatrix a12) + (z * aMatrix a13). ry := (x * aMatrix a21) + (y * aMatrix a22) + (z * aMatrix a23). rz := (x * aMatrix a31) + (y * aMatrix a32) + (z * aMatrix a33). scaleNeeded ifTrue:[ dot _ (rx * rx) + (ry * ry) + (rz * rz). dot < 1.0e-20 ifTrue:[ rx _ ry _ rz _ 0.0. ] ifFalse:[ dot = 1.0 ifFalse:[ dot _ 1.0 / dot sqrt. rx _ rx * dot. ry _ ry * dot. rz _ rz * dot. ]. ]. ]. primitiveVertex normalX: rx. primitiveVertex normalY: ry. primitiveVertex normalZ: rz.! !!B3DVertexTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:20'!privateTransformPrimitiveVertex: primitiveVertex byModelView: aMatrix | x y z rx ry rz rw oneOverW | x _ primitiveVertex positionX. y _ primitiveVertex positionY. z _ primitiveVertex positionZ. rx := (x * aMatrix a11) + (y * aMatrix a12) + (z * aMatrix a13) + aMatrix a14. ry := (x * aMatrix a21) + (y * aMatrix a22) + (z * aMatrix a23) + aMatrix a24. rz := (x * aMatrix a31) + (y * aMatrix a32) + (z * aMatrix a33) + aMatrix a34. rw := (x * aMatrix a41) + (y * aMatrix a42) + (z * aMatrix a43) + aMatrix a44. rw = 1.0 ifTrue:[ primitiveVertex positionX: rx. primitiveVertex positionY: ry. primitiveVertex positionZ: rz. ] ifFalse:[ rw = 0.0 ifTrue:[oneOverW _ 0.0] ifFalse:[oneOverW _ 1.0 / rw]. primitiveVertex positionX: rx * oneOverW. primitiveVertex positionY: ry * oneOverW. primitiveVertex positionZ: rz * oneOverW. ].! !!B3DVertexTransformer methodsFor: 'private-transforming' stamp: 'ar 2/8/1999 18:19'!privateTransformPrimitiveVertex: primitiveVertex byModelViewWithoutW: aMatrix "Special case of aMatrix a41 = a42 = a43 = 0.0 and a44 = 1.0" | x y z rx ry rz | "Note: This is not supported by primitive level operations." self flag: #b3dPrimitive. x _ primitiveVertex positionX. y _ primitiveVertex positionY. z _ primitiveVertex positionZ. rx := (x * aMatrix a11) + (y * aMatrix a12) + (z * aMatrix a13) + aMatrix a14. ry := (x * aMatrix a21) + (y * aMatrix a22) + (z * aMatrix a23) + aMatrix a24. rz := (x * aMatrix a31) + (y * aMatrix a32) + (z * aMatrix a33) + aMatrix a34. primitiveVertex positionX: rx. primitiveVertex positionY: ry. primitiveVertex positionZ: rz.! !!B3DVertexTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:21'!privateTransformPrimitiveVertex: primitiveVertex byProjection: aMatrix | x y z rx ry rz rw | x _ primitiveVertex positionX. y _ primitiveVertex positionY. z _ primitiveVertex positionZ. rx := (x * aMatrix a11) + (y * aMatrix a12) + (z * aMatrix a13) + aMatrix a14. ry := (x * aMatrix a21) + (y * aMatrix a22) + (z * aMatrix a23) + aMatrix a24. rz := (x * aMatrix a31) + (y * aMatrix a32) + (z * aMatrix a33) + aMatrix a34. rw := (x * aMatrix a41) + (y * aMatrix a42) + (z * aMatrix a43) + aMatrix a44. primitiveVertex rasterPosX: rx. primitiveVertex rasterPosY: ry. primitiveVertex rasterPosZ: rz. primitiveVertex rasterPosW: rw.! !!B3DVertexTransformer methodsFor: 'private-transforming' stamp: 'ar 2/17/1999 04:22'!privateTransformVB: vertexArray count: vertexCount modelViewMatrix: modelViewMatrix projectionMatrix: projectionMatrix flags: flags | noW | (modelViewMatrix a41 = 0.0 and:[ modelViewMatrix a42 = 0.0 and:[ modelViewMatrix a43 = 0.0 and:[ modelViewMatrix a44 = 1.0]]]) ifTrue:[noW _ true]. noW ifTrue:[ vertexArray upTo: vertexCount do:[:primitiveVertex| self privateTransformPrimitiveVertex: primitiveVertex byModelViewWithoutW: modelViewMatrix. self privateTransformPrimitiveVertex: primitiveVertex byProjection: projectionMatrix. (flags anyMask: VBVtxHasNormals) ifTrue:[self privateTransformPrimitiveNormal: primitiveVertex byMatrix: modelViewMatrix rescale: true]. ]. ] ifFalse:[ vertexArray upTo: vertexCount do:[:primitiveVertex| self privateTransformPrimitiveVertex: primitiveVertex byModelView: modelViewMatrix. self privateTransformPrimitiveVertex: primitiveVertex byProjection: projectionMatrix. (flags anyMask: VBVtxHasNormals) ifTrue:[self privateTransformPrimitiveNormal: primitiveVertex byMatrix: modelViewMatrix rescale: true]. ]. ].! !!B3DVertexTransformer class methodsFor: 'testing' stamp: 'ar 2/14/1999 01:41'!isAvailable "Return true if this part of the engine is available" ^true! !I represent a viewing frustum, defined by the following values:
-
- typedef struct B3DViewingFrustum {
- float left;
- float right;
- float top;
- float bottom;
- float near;
- float far;
- } B3DViewingFrustum;
-
- The frustum can be converted into either a ortho matrix (having no perspective distortion) or a perspective matrix for use in the Balloon 3D render engine.!!B3DViewingFrustum methodsFor: 'private'!asOrthoMatrixInto: aB3DMatrix4x4 | x y z tx ty tz dx dy dz | (self near <= 0.0 or:[self far <= 0.0]) ifTrue: [^self error:'Clipping plane error']. dx := self right - self left. dy := self top - self bottom. dz := self far - self near. x := dx * 0.5. y := dy * 0.5. z := dz * -0.5. tx := (self left + self right) / dx. ty := (self top + self bottom) / dy. tz := (self near + self far) / dz. aB3DMatrix4x4 a11: x; a12: 0.0; a13: 0.0; a14: tx; a21: 0.0; a22: y; a23: 0.0; a24: ty; a31: 0.0; a32: 0.0; a33: z; a34: tz; a41: 0.0; a42: 0.0; a43: 0.0; a44: 1.0. ^aB3DMatrix4x4! !!B3DViewingFrustum methodsFor: 'private' stamp: 'ar 2/7/1999 01:30'!asPerspectiveMatrixInto: aB3DMatrix4x4 | x y a b c d dx dy dz z2 | (self near <= 0.0 or:[self far <= 0.0 or:[self near >= self far]]) ifTrue: [^self error:'Clipping plane error']. dx := self right - self left. dy := self top - self bottom. dz := self far - self near. z2 := 2.0 * self near. x := z2 / dx. y := z2 / dy. a := (self left + self right) / dx. b := (self top + self bottom) / dy. c := (self near + self far) "*negated*" / dz. d := (-2.0 * self near * self far) / dz. aB3DMatrix4x4 a11: x; a12: 0.0; a13: a; a14: 0.0; a21: 0.0; a22: y; a23: b; a24: 0.0; a31: 0.0; a32: 0.0; a33: c; a34: d; a41: 0.0; a42: 0.0; a43: "*-1*"1; a44: 0.0. ^aB3DMatrix4x4! !!B3DViewingFrustum methodsFor: 'private'!computeFromNear: nearDistance far: farDistance fov: fieldOfView aspect: aspectRatio "Compute the viewing frustum from the given values" | top bottom | top := nearDistance * fieldOfView degreesToRadians tan. bottom := top negated. self left: bottom * aspectRatio. self right: top * aspectRatio. self top: top. self bottom: bottom. self near: nearDistance. self far: farDistance.! !!B3DViewingFrustum methodsFor: 'accessing'!bottom ^self floatAt: 4.! !!B3DViewingFrustum methodsFor: 'accessing'!bottom: aFloat self floatAt: 4 put: aFloat! !!B3DViewingFrustum methodsFor: 'accessing'!far ^self floatAt: 6! !!B3DViewingFrustum methodsFor: 'accessing'!far: aFloat self floatAt: 6 put: aFloat! !!B3DViewingFrustum methodsFor: 'accessing'!left ^self floatAt: 1! !!B3DViewingFrustum methodsFor: 'accessing'!left: aFloat self floatAt: 1 put: aFloat! !!B3DViewingFrustum methodsFor: 'accessing'!near ^self floatAt: 5! !!B3DViewingFrustum methodsFor: 'accessing'!near: aFloat self floatAt: 5 put: aFloat! !!B3DViewingFrustum methodsFor: 'accessing'!right ^self floatAt: 2! !!B3DViewingFrustum methodsFor: 'accessing'!right: aFloat self floatAt: 2 put: aFloat! !!B3DViewingFrustum methodsFor: 'accessing'!top ^self floatAt: 3! !!B3DViewingFrustum methodsFor: 'accessing'!top: aFloat self floatAt: 3 put: aFloat! !!B3DViewingFrustum methodsFor: 'converting'!asFrustum ^self! !!B3DViewingFrustum methodsFor: 'converting'!asOrthoMatrix ^self asOrthoMatrixInto: B3DMatrix4x4 new! !!B3DViewingFrustum methodsFor: 'converting'!asPerspectiveMatrix ^self asPerspectiveMatrixInto: B3DMatrix4x4 new! !!B3DViewingFrustum class methodsFor: 'instance creation'!near: nearDistance far: farDistance fov: fieldOfView aspect: aspectRatio ^self new computeFromNear: nearDistance far: farDistance fov: fieldOfView aspect: aspectRatio! !!B3DViewingFrustum class methodsFor: 'instance creation'!numElements ^6! !I represent a viewport for the Ballon 3D graphics engine. Since all positions are computed in the unit-coordinate system (-1,-1,-1) (1,1,1) after the render pipeline has completed, I am used to map these positions into the physical (pixel) coordinates of the output device before rasterization takes place.Instance variables: center <Point> The center of the viewport scale <Point> The scale for points!!B3DViewport methodsFor: 'mapping'!asMatrixTransform2x3 ^(MatrixTransform2x3 withScale: scale) offset: center! !!B3DViewport methodsFor: 'mapping'!mapVertex4: aVector | w x y oneOverW | w _ aVector w. w = 1.0 ifTrue:[ x _ aVector x. y _ aVector y. ] ifFalse:[ w = 0.0 ifTrue:[oneOverW _ 0.0] ifFalse:[oneOverW _ 1.0 / w]. x _ aVector x * oneOverW. y _ aVector y * oneOverW. ]. ^((x@y) * scale + center) truncated! !!B3DViewport methodsFor: 'private' stamp: 'ar 2/8/1999 21:45'!setOrigin: topLeft corner: bottomRight super setOrigin: topLeft corner: bottomRight. center _ (self origin + self corner) / 2.0. scale _ corner - center + (0.5@-0.5). "Rasterizer offset"! !!B3DViewport methodsFor: 'private' stamp: 'ar 2/7/1999 01:42'!toggleYScale scale _ scale x @ scale y negated.! !!B3DViewport methodsFor: 'accessing' stamp: 'ar 2/15/1999 02:53'!aspectRatio ^self width asFloat / self height asFloat! !!B3DViewport methodsFor: 'accessing' stamp: 'ar 4/3/1999 20:29'!center ^center! !!B3DViewport methodsFor: 'accessing' stamp: 'ar 4/3/1999 20:29'!scale ^scale! !This morph incorporates tiling and regular motion with the intent of supporting, eg, panning of endless (toroidal) backgrounds.The idea is that embedded morphs get displayed at a moving offset relative to my position. Moreover this display is tiled according to the bounding box of the submorphs (subBounds), as much as necesary to fill the rest of my bounds.!!BackgroundMorph methodsFor: 'as yet unclassified' stamp: 'ar 6/17/1999 01:06'!drawOn: aCanvas "The tiling is solely determined by bounds, subBounds and offset. The extent of display is determined by bounds and the clipRect of the canvas." | start d subBnds | submorphs isEmpty ifTrue: [^ super drawOn: aCanvas]. subBnds _ self subBounds. running ifFalse: [super drawOn: aCanvas. ^ aCanvas fillRectangle: subBnds color: Color lightBlue]. start _ subBnds topLeft + offset - bounds topLeft - (1@1) \\ subBnds extent - subBnds extent + (1@1). d _ subBnds topLeft - bounds topLeft."Sensor redButtonPressed ifTrue: [self halt]." start x to: bounds width - 1 by: subBnds width do: [:x | start y to: bounds height - 1 by: subBnds height do: [:y | aCanvas translateBy: (x@y) - d clippingTo: bounds during:[:tileCanvas| self drawSubmorphsOn: tileCanvas]]].! !!BackgroundMorph methodsFor: 'as yet unclassified' stamp: 'ar 5/29/1999 08:32'!fullDrawOn: aCanvas running ifFalse: [ ^aCanvas clipBy: (bounds translateBy: aCanvas origin) during:[:clippedCanvas| super fullDrawOn: clippedCanvas]]. aCanvas drawMorph: self.! !I represent an unordered collection of possibly duplicate elements. I store these elements in a dictionary, tallying up occurrences of equal objects. Because I store an occurrence only once, my clients should beware that objects they store will not necessarily be retrieved such that == is true. If the client cares, a subclass of me should be created.!!Bag methodsFor: 'accessing' stamp: 'sma 5/12/2000 17:23'!at: index self errorNotKeyed! !!Bag methodsFor: 'accessing' stamp: 'sma 5/12/2000 17:23'!at: index put: anObject self errorNotKeyed! !!Bag methodsFor: 'accessing' stamp: 'tao 1/5/2000 18:25'!cumulativeCounts "Answer with a collection of cumulative percents covered by elements so far." | s n | s _ self size / 100.0. n _ 0. ^ self sortedCounts asArray collect: [:a | n _ n + a key. (n / s roundTo: 0.1) -> a value]! !!Bag methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:35'!size "Answer how many elements the receiver contains." | tally | tally _ 0. contents do: [:each | tally _ tally + each]. ^ tally! !!Bag methodsFor: 'adding' stamp: 'sma 5/12/2000 17:18'!add: newObject "Include newObject as one of the receiver's elements. Answer newObject." ^ self add: newObject withOccurrences: 1! !!Bag methodsFor: 'adding' stamp: 'sma 5/12/2000 17:20'!add: newObject withOccurrences: anInteger "Add newObject anInteger times to the receiver. Answer newObject." contents at: newObject put: (contents at: newObject ifAbsent: [0]) + anInteger. ^ newObject! !!Bag methodsFor: 'converting' stamp: 'sma 5/12/2000 14:34'!asBag ^ self! !!Bag methodsFor: 'converting' stamp: 'sma 5/12/2000 14:30'!asSet "Answer a set with the elements of the receiver." ^ contents keys! !!Bag methodsFor: 'copying' stamp: 'sma 5/12/2000 14:53'!copy ^ self shallowCopy setContents: contents copy! !!Bag methodsFor: 'private' stamp: 'sma 5/12/2000 14:49'!setContents: aDictionary contents _ aDictionary! !!Bag methodsFor: 'removing' stamp: 'sma 5/12/2000 14:32'!remove: oldObject ifAbsent: exceptionBlock "Refer to the comment in Collection|remove:ifAbsent:." | count | count _ contents at: oldObject ifAbsent: [^ exceptionBlock value]. count = 1 ifTrue: [contents removeKey: oldObject] ifFalse: [contents at: oldObject put: count - 1]. ^ oldObject! !!Bag class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 13:31'!new ^ self new: 4! !!Bag class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 14:49'!new: nElements ^ super new setContents: (Dictionary new: nElements)! !!Bag class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 17:17'!newFrom: aCollection "Answer an instance of me containing the same elements as aCollection." ^ self withAll: aCollection"Examples: Bag newFrom: {1. 2. 3. 3} {1. 2. 3. 3} as: Bag"! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!end ^end! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!end: aPoint end _ aPoint! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 01:57'!inTangent "Return the tangent at the start point" ^via - start! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!initialX ^start y <= end y ifTrue:[start x] ifFalse:[end x]! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!initialY ^start y <= end y ifTrue:[start y] ifFalse:[end y]! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!initialZ ^0 "Assume no depth given"! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 01:57'!outTangent "Return the tangent at the end point" ^end - via! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!start ^start! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!start: aPoint start _ aPoint! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!via ^via! !!BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'!via: aPoint via _ aPoint! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 20:46'!computeInitialStateFrom: source with: transformation "Compute the initial state in the receiver." start _ (transformation localPointToGlobal: source start) asIntegerPoint. end _ (transformation localPointToGlobal: source end) asIntegerPoint. via _ (transformation localPointToGlobal: source via) asIntegerPoint.! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 02:39'!computeSplitAt: t "Split the receiver at the parametric value t" | left right newVia1 newVia2 newPoint | left _ self clone. right _ self clone. "Compute new intermediate points" newVia1 _ (via - start) * t + start. newVia2 _ (end - via) * t + via. "Compute new point on curve" newPoint _ ((newVia1 - newVia2) * t + newVia2) asIntegerPoint. left via: newVia1 asIntegerPoint. left end: newPoint. right start: newPoint. right via: newVia2 asIntegerPoint. ^Array with: left with: right! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 01:34'!floatStepToFirstScanLineAt: yValue in: edgeTableEntry "Float version of forward differencing" | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 steps scaledStepSize squaredStepSize | (end y) >= (start y) ifTrue:[ startX _ start x. endX _ end x. startY _ start y. endY _ end y. ] ifFalse:[ startX _ end x. endX _ start x. startY _ end y. endY _ start y. ]. deltaY _ endY - startY. "Quickly check if the line is visible at all" (yValue >= endY or:[deltaY = 0]) ifTrue:[ ^edgeTableEntry lines: 0]. fwX1 _ (startX + endX - (2 * via x)) asFloat. fwX2 _ (via x - startX * 2) asFloat. fwY1 _ (startY + endY - (2 * via y)) asFloat. fwY2 _ ((via y - startY) * 2) asFloat. steps _ deltaY asInteger * 2. scaledStepSize _ 1.0 / steps asFloat. squaredStepSize _ scaledStepSize * scaledStepSize. fwDx _ fwX2 * scaledStepSize. fwDDx _ 2.0 * fwX1 * squaredStepSize. fwDy _ fwY2 * scaledStepSize. fwDDy _ 2.0 * fwY1 * squaredStepSize. fwDx _ fwDx + (fwDDx * 0.5). fwDy _ fwDy + (fwDDy * 0.5). lastX _ startX asFloat. lastY _ startY asFloat. "self xDirection: xDir. self yDirection: yDir." edgeTableEntry xValue: startX. edgeTableEntry yValue: startY. edgeTableEntry zValue: 0. edgeTableEntry lines: deltaY. "If not at first scan line then step down to yValue" yValue = startY ifFalse:[ self stepToNextScanLineAt: yValue in: edgeTableEntry. "And adjust remainingLines" edgeTableEntry lines: deltaY - (yValue - startY). ].! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 02:45'!floatStepToNextScanLineAt: yValue in: edgeTableEntry "Float version of forward differencing" [yValue asFloat > lastY] whileTrue:[ (fwDx < -50.0 or:[fwDx > 50.0]) ifTrue:[self halt]. (fwDy < -50.0 or:[fwDy > 50.0]) ifTrue:[self halt]. (fwDDx < -50.0 or:[fwDDx > 50.0]) ifTrue:[self halt]. (fwDDy < -50.0 or:[fwDDy > 50.0]) ifTrue:[self halt]. lastX _ lastX + fwDx. lastY _ lastY + fwDy. fwDx _ fwDx + fwDDx. fwDy _ fwDy + fwDDy. ]. edgeTableEntry xValue: lastX asInteger. edgeTableEntry zValue: 0.! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 16:23'!intStepToFirstScanLineAt: yValue in: edgeTableEntry "Scaled integer version of forward differencing" | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 scaledStepSize squaredStepSize | (end y) >= (start y) ifTrue:[ startX _ start x. endX _ end x. startY _ start y. endY _ end y. ] ifFalse:[ startX _ end x. endX _ start x. startY _ end y. endY _ start y. ]. deltaY _ endY - startY. "Quickly check if the line is visible at all" (yValue >= endY or:[deltaY = 0]) ifTrue:[ ^edgeTableEntry lines: 0]. fwX1 _ (startX + endX - (2 * via x)). fwX2 _ (via x - startX * 2). fwY1 _ (startY + endY - (2 * via y)). fwY2 _ ((via y - startY) * 2). maxSteps _ deltaY asInteger * 2. scaledStepSize _ 16r1000000 // maxSteps. "@@: Okay, we need some fancy 64bit multiplication here" squaredStepSize _ self absoluteSquared8Dot24: scaledStepSize. squaredStepSize = ((scaledStepSize * scaledStepSize) bitShift: -24) ifFalse:[self error:'Bad computation']. fwDx _ fwX2 * scaledStepSize. fwDDx _ 2 * fwX1 * squaredStepSize. fwDy _ fwY2 * scaledStepSize. fwDDy _ 2 * fwY1 * squaredStepSize. fwDx _ fwDx + (fwDDx // 2). fwDy _ fwDy + (fwDDy // 2). self validateIntegerRange. lastX _ startX * 256. lastY _ startY * 256. edgeTableEntry xValue: startX. edgeTableEntry yValue: startY. edgeTableEntry zValue: 0. edgeTableEntry lines: deltaY. "If not at first scan line then step down to yValue" yValue = startY ifFalse:[ self stepToNextScanLineAt: yValue in: edgeTableEntry. "And adjust remainingLines" edgeTableEntry lines: deltaY - (yValue - startY). ].! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 04:02'!intStepToNextScanLineAt: yValue in: edgeTableEntry "Scaled integer version of forward differencing" [maxSteps >= 0 and:[yValue * 256 > lastY]] whileTrue:[ self validateIntegerRange. lastX _ lastX + ((fwDx + 16r8000) // 16r10000). lastY _ lastY + ((fwDy + 16r8000) // 16r10000). fwDx _ fwDx + fwDDx. fwDy _ fwDy + fwDDy. maxSteps _ maxSteps - 1. ]. edgeTableEntry xValue: lastX // 256. edgeTableEntry zValue: 0.! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/29/1998 22:14'!isMonoton "Return true if the receiver is monoton along the y-axis, e.g., check if the tangents have the same sign" ^(via y - start y) * (end y - via y) >= 0! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/31/1998 16:36'!stepToFirstScanLineAt: yValue in: edgeTableEntry "Compute the initial x value for the scan line at yValue" ^self intStepToFirstScanLineAt: yValue in: edgeTableEntry! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 03:40'!stepToNextScanLineAt: yValue in: edgeTableEntry "Compute the next x value for the scan line at yValue. This message is sent during incremental updates. The yValue parameter is passed in here for edges that have more complicated computations," ^self intStepToNextScanLineAt: yValue in: edgeTableEntry! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 11/1/1998 00:31'!subdivide "Subdivide the receiver" | dy dx | "Test 1: If the bezier curve is not monoton in Y, we need a subdivision" self isMonoton ifFalse:[ MonotonSubdivisions _ MonotonSubdivisions + 1. ^self subdivideToBeMonoton]. "Test 2: If the receiver is horizontal, don't do anything" (end y = start y) ifTrue:[^nil]. "Test 3: If the receiver can be represented as a straight line, make a line from the receiver and declare it invalid" ((end - start) crossProduct: (via - start)) = 0 ifTrue:[ LineConversions _ LineConversions + 1. ^self subdivideToBeLine]. "Test 4: If the height of the curve exceeds 256 pixels, subdivide (forward differencing is numerically not very stable)" dy _ end y - start y. dy < 0 ifTrue:[dy _ dy negated]. (dy > 255) ifTrue:[ HeightSubdivisions _ HeightSubdivisions + 1. ^self subdivideAt: 0.5]. "Test 5: Check if the incremental values could possibly overflow the scaled integer range" dx _ end x - start x. dx < 0 ifTrue:[dx _ dx negated]. dy * 32 < dx ifTrue:[ OverflowSubdivisions _ OverflowSubdivisions + 1. ^self subdivideAt: 0.5]. ^nil! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 22:13'!subdivideAt: parameter "Subdivide the receiver at the given parameter" | both | (parameter <= 0.0 or:[parameter >= 1.0]) ifTrue:[self halt]. both _ self computeSplitAt: parameter. "Transcript cr. self quickPrint: self. Transcript space. self quickPrint: both first. Transcript space. self quickPrint: both last. Transcript endEntry." self via: both first via. self end: both first end. ^both last! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 11/11/1998 22:15'!subdivideToBeLine "Not a true subdivision. Just return a line representing the receiver and fake me to be of zero height" | line | line _ BalloonLineSimulation new. line start: start. line end: end. "Make me invalid" end _ start. via _ start. ^line! !!BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 02:24'!subdivideToBeMonoton "Subdivide the receiver at it's extreme point" | v1 v2 t other | v1 _ (via - start). v2 _ (end - via). t _ (v1 y / (v2 y - v1 y)) negated asFloat. other _ self subdivideAt: t. self isMonoton ifFalse:[self halt]. other isMonoton ifFalse:[self halt]. ^other! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 16:37'!absoluteSquared8Dot24: value "Compute the squared value of a 8.24 number with 0.0 <= value < 1.0, e.g., compute (value * value) bitShift: -24" | halfWord1 halfWord2 result | (value >= 0 and:[value < 16r1000000]) ifFalse:[^self error:'Value out of range']. halfWord1 _ value bitAnd: 16rFFFF. halfWord2 _ (value bitShift: -16) bitAnd: 255. result _ (halfWord1 * halfWord1) bitShift: -16. "We don't need the lower 16bits at all" result _ result + ((halfWord1 * halfWord2) * 2). result _ result + ((halfWord2 * halfWord2) bitShift: 16). "word1 _ halfWord1 * halfWord1. word2 _ (halfWord2 * halfWord1) + (word1 bitShift: -16). word1 _ word1 bitAnd: 16rFFFF. word2 _ word2 + (halfWord1 * halfWord2). word2 _ word2 + ((halfWord2 * halfWord2) bitShift: 16)." ^result bitShift: -8! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 5/25/2000 17:57'!debugDraw | entry minY maxY lX lY canvas | entry _ BalloonEdgeData new. canvas _ Display getCanvas. minY _ (start y min: end y) min: via y. maxY _ (start y max: end y) max: via y. entry yValue: minY. self stepToFirstScanLineAt: minY in: entry. lX _ entry xValue. lY _ entry yValue. minY+1 to: maxY do:[:y| self stepToNextScanLineAt: y in: entry. canvas line: lX@lY to: entry xValue @ y width: 2 color: Color black. lX _ entry xValue. lY _ y. ].! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 5/25/2000 17:57'!debugDraw2 | canvas last max t next | canvas _ Display getCanvas. max _ 100. last _ nil. 0 to: max do:[:i| t _ i asFloat / max asFloat. next _ self valueAt: t. last ifNotNil:[ canvas line: last to: next rounded width: 2 color: Color blue. ]. last _ next rounded. ].! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 5/25/2000 17:57'!debugDrawWide: n | entry minY maxY canvas curve p1 p2 entry2 y | curve _ self class new. curve start: start + (0@n). curve via: via + (0@n). curve end: end + (0@n). entry _ BalloonEdgeData new. entry2 _ BalloonEdgeData new. canvas _ Display getCanvas. minY _ (start y min: end y) min: via y. maxY _ (start y max: end y) max: via y. entry yValue: minY. entry2 yValue: minY + n. self stepToFirstScanLineAt: minY in: entry. curve stepToFirstScanLineAt: minY+n in: entry2. y _ minY. 1 to: n do:[:i| y _ y + 1. self stepToNextScanLineAt: y in: entry. p1 _ entry xValue @ y. canvas line: p1 to: p1 + (n@0) width: 1 color: Color black. ]. [y < maxY] whileTrue:[ y _ y + 1. self stepToNextScanLineAt: y in: entry. p2 _ (entry xValue + n) @ y. curve stepToNextScanLineAt: y in: entry2. p1 _ entry2 xValue @ y. canvas line: p1 to: p2 width: 1 color: Color black. ].! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 00:35'!printOn: aStream aStream nextPutAll: self class name; nextPut:$(; print: start; nextPutAll:' - '; print: via; nextPutAll:' - '; print: end; nextPut:$)! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'MPW 1/1/1901 21:55'!printOnStream: aStream aStream print: self class name; print:'('; write: start; print:' - '; write: via; print:' - '; write: end; print:')'.! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 21:56'!quickPrint: curve Transcript nextPut:$(; print: curve start; space; print: curve via; space; print: curve end; nextPut:$).! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 22:13'!quickPrint: curve first: aBool aBool ifTrue:[Transcript cr]. Transcript nextPut:$(; print: curve start; space; print: curve via; space; print: curve end; nextPut:$). Transcript endEntry.! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 03:53'!stepToFirst | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 steps scaledStepSize squaredStepSize | (end y) >= (start y) ifTrue:[ startX _ start x. endX _ end x. startY _ start y. endY _ end y. ] ifFalse:[ startX _ end x. endX _ start x. startY _ end y. endY _ start y. ]. deltaY _ endY - startY. "Quickly check if the line is visible at all" (deltaY = 0) ifTrue:[^self]. fwX1 _ (startX + endX - (2 * via x)) asFloat. fwX2 _ (via x - startX * 2) asFloat. fwY1 _ (startY + endY - (2 * via y)) asFloat. fwY2 _ ((via y - startY) * 2) asFloat. steps _ deltaY asInteger * 2. scaledStepSize _ 1.0 / steps asFloat. squaredStepSize _ scaledStepSize * scaledStepSize. fwDx _ fwX2 * scaledStepSize. fwDDx _ 2.0 * fwX1 * squaredStepSize. fwDy _ fwY2 * scaledStepSize. fwDDy _ 2.0 * fwY1 * squaredStepSize. fwDx _ fwDx + (fwDDx * 0.5). fwDy _ fwDy + (fwDDy * 0.5). lastX _ startX asFloat. lastY _ startY asFloat.! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 03:50'!stepToFirstInt "Scaled integer version of forward differencing" | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 scaledStepSize squaredStepSize | self halt. (end y) >= (start y) ifTrue:[ startX _ start x. endX _ end x. startY _ start y. endY _ end y. ] ifFalse:[ startX _ end x. endX _ start x. startY _ end y. endY _ start y. ]. deltaY _ endY - startY. "Quickly check if the line is visible at all" (deltaY = 0) ifTrue:[^nil]. fwX1 _ (startX + endX - (2 * via x)). fwX2 _ (via x - startX * 2). fwY1 _ (startY + endY - (2 * via y)). fwY2 _ ((via y - startY) * 2). maxSteps _ deltaY asInteger * 2. scaledStepSize _ 16r1000000 // maxSteps. "@@: Okay, we need some fancy 64bit multiplication here" squaredStepSize _ (scaledStepSize * scaledStepSize) bitShift: -24. fwDx _ fwX2 * scaledStepSize. fwDDx _ 2 * fwX1 * squaredStepSize. fwDy _ fwY2 * scaledStepSize. fwDDy _ 2 * fwY1 * squaredStepSize. fwDx _ fwDx + (fwDDx // 2). fwDy _ fwDy + (fwDDy // 2). self validateIntegerRange. lastX _ startX * 256. lastY _ startY * 256.! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 00:26'!stepToNext lastX _ lastX + fwDx. lastY _ lastY + fwDy. fwDx _ fwDx + fwDDx. fwDy _ fwDy + fwDDy.! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 04:01'!stepToNextInt "Scaled integer version of forward differencing" self halt. (maxSteps >= 0) ifTrue:[ self validateIntegerRange. lastX _ lastX + ((fwDx + 16r8000) // 16r10000). lastY _ lastY + ((fwDy + 16r8000) // 16r10000). fwDx _ fwDx + fwDDx. fwDy _ fwDy + fwDDy. maxSteps _ maxSteps - 1. ].! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 03:27'!validateIntegerRange fwDx class == SmallInteger ifFalse:[self halt]. fwDy class == SmallInteger ifFalse:[self halt]. fwDDx class == SmallInteger ifFalse:[self halt]. fwDDy class == SmallInteger ifFalse:[self halt].! !!BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/29/1998 21:26'!valueAt: parameter "Return the point at the value parameter: p(t) = (1-t)^2 * p1 + 2*t*(1-t) * p2 + t^2 * p3. " | t1 t2 t3 | t1 _ (1.0 - parameter) squared. t2 _ 2 * parameter * (1.0 - parameter). t3 _ parameter squared. ^(start * t1) + (via * t2) + (end * t3)! !!BalloonBezierSimulation class methodsFor: 'class initialization' stamp: 'ar 10/30/1998 03:04'!initialize "GraphicsBezierSimulation initialize" HeightSubdivisions _ 0. LineConversions _ 0. MonotonSubdivisions _ 0. OverflowSubdivisions _ 0.! !!BalloonBuffer methodsFor: 'accessing' stamp: 'ar 10/26/1998 21:12'!at: index "For simulation only" | word | word _ self basicAt: index. word < 16r3FFFFFFF ifTrue:[^word]. "Avoid LargeInteger computations" ^word >= 16r80000000 "Negative?!!" ifTrue:["word - 16r100000000" (word bitInvert32 + 1) negated] ifFalse:[word]! !!BalloonBuffer methodsFor: 'accessing' stamp: 'ar 10/26/1998 21:12'!at: index put: anInteger "For simulation only" | word | anInteger < 0 ifTrue:["word _ 16r100000000 + anInteger" word _ (anInteger + 1) negated bitInvert32] ifFalse:[word _ anInteger]. self basicAt: index put: word. ^anInteger! !!BalloonBuffer methodsFor: 'accessing' stamp: 'ar 2/4/1999 17:04'!floatAt: index "For simulation only" <primitive: 'primitiveFloatArrayAt'> ^Float fromIEEE32Bit: (self basicAt: index)! !!BalloonBuffer methodsFor: 'accessing' stamp: 'ar 2/4/1999 17:06'!floatAt: index put: value "For simulation only" <primitive: 'primitiveFloatArrayAtPut'> value isFloat ifTrue:[self basicAt: index put: value asIEEE32BitWord] ifFalse:[self at: index put: value asFloat]. ^value! !!BalloonBuffer class methodsFor: 'instance creation' stamp: 'ar 10/26/1998 21:11'!mew: n ^self new: (n max: 256)! !!BalloonBuffer class methodsFor: 'instance creation' stamp: 'ar 10/26/1998 21:11'!new ^self new: 256.! !!BalloonCanvas methodsFor: 'initialize' stamp: 'ar 11/24/1998 15:28'!flush "Force all pending primitives onscreen" engine ifNotNil:[engine flush].! !!BalloonCanvas methodsFor: 'initialize' stamp: 'ar 12/30/1998 10:54'!initialize aaLevel _ 1. deferred _ false.! !!BalloonCanvas methodsFor: 'initialize' stamp: 'ar 11/11/1998 20:25'!resetEngine engine _ nil.! !!BalloonCanvas methodsFor: 'accessing' stamp: 'ar 11/13/1998 01:02'!aaLevel ^aaLevel! !!BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:53'!aaLevel: newLevel "Only allow changes to aaLevel if we're working on >= 8 bit forms" form depth >= 8 ifFalse:[^self]. aaLevel = newLevel ifTrue:[^self]. self flush. "In case there are pending primitives in the engine" aaLevel _ newLevel. engine ifNotNil:[engine aaLevel: aaLevel].! !!BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:54'!deferred ^deferred! !!BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:55'!deferred: aBoolean deferred == aBoolean ifTrue:[^self]. self flush. "Force pending prims on screen" deferred _ aBoolean. engine ifNotNil:[engine deferred: aBoolean].! !!BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:55'!ensuredEngine engine ifNil:[ true ifTrue:[engine _ BalloonEngine new] ifFalse:[engine _ BalloonDebugEngine new]. engine aaLevel: aaLevel. engine bitBlt: port. engine destOffset: origin. engine clipRect: clipRect. engine deferred: deferred. engine]. engine colorTransform: colorTransform. engine edgeTransform: transform. ^engine! !!BalloonCanvas methodsFor: 'testing' stamp: 'ar 11/13/1998 13:19'!isBalloonCanvas ^true! !!BalloonCanvas methodsFor: 'testing' stamp: 'ar 11/12/1998 01:07'!isVisible: aRectangle ^transform ifNil:[super isVisible: aRectangle] ifNotNil:[super isVisible: (transform localBoundsToGlobal: aRectangle)]! !!BalloonCanvas methodsFor: 'copying' stamp: 'ar 11/24/1998 22:33'!copy self flush. ^super copy resetEngine! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:40'!fillColor: c "Note: This always fills, even if the color is transparent." "Note2: To achieve the above we must make sure that c is NOT transparent" self frameAndFillRectangle: form boundingBox fillColor: (c alpha: 1.0) borderWidth: 0 borderColor: nil! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:51'!fillOval: r color: c borderWidth: borderWidth borderColor: borderColor "Draw a filled and outlined oval" "Note: The optimization test below should actually read: self ifNoTransformWithIn: (r insetBy: borderWidth // 2) but since borderWidth is assumed to be very small related to r we don't check it." (self ifNoTransformWithIn: r) ifTrue:[^super fillOval: r color: c borderWidth: borderWidth borderColor: borderColor]. ^self drawOval: (r insetBy: borderWidth // 2) color: c borderWidth: borderWidth borderColor: borderColor! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:40'!fillRectangle: r color: c "Fill the rectangle with the given color" ^self frameAndFillRectangle: r fillColor: c borderWidth: 0 borderColor: nil! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 06:26'!frameAndFillRectangle: r fillColor: c borderWidth: borderWidth borderColor: borderColor "Draw a filled and outlined rectangle" "Note: The optimization test below should actually read: self ifNoTransformWithIn: (r insetBy: borderWidth // 2) but since borderWidth is assumed to be very small related to r we don't check it." (self ifNoTransformWithIn: r) ifTrue:[^super frameAndFillRectangle: r fillColor: c borderWidth: borderWidth borderColor: borderColor]. ^self drawRectangle: (r insetBy: borderWidth // 2) color: c borderWidth: borderWidth borderColor: borderColor! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:52'!frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor "Draw a beveled or raised rectangle" | bw | "Note: The optimization test below should actually read: self ifNoTransformWithIn: (r insetBy: borderWidth // 2) but since borderWidth is assumed to be very small related to r we don't check it." (self ifNoTransformWithIn: r) ifTrue:[^super frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor]. "Fill rectangle and draw top and left border" bw _ borderWidth // 2. self drawRectangle: (r insetBy: bw) color: fillColor borderWidth: borderWidth borderColor: topLeftColor. "Now draw bottom right border." self drawPolygon: (Array with: r topRight + (bw negated@bw) with: r bottomRight - bw asPoint with: r bottomLeft + (bw@bw negated)) color: nil borderWidth: borderWidth borderColor: bottomRightColor.! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:41'!frameRectangle: r width: w color: c "Draw a frame around the given rectangle" ^self frameAndFillRectangle: r fillColor: nil borderWidth: w borderColor: c! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/12/1999 17:45'!line: pt1 to: pt2 width: w color: c "Draw a line from pt1 to: pt2" (self ifNoTransformWithIn:(pt1 rect: pt2)) ifTrue:[^super line: pt1 to: pt2 width: w color: c]. ^self drawPolygon: (Array with: pt1 with: pt2) color: c borderWidth: w borderColor: c! !!BalloonCanvas methodsFor: 'drawing' stamp: 'ar 11/11/1998 19:39'!point: pt color: c "Is there any use for this?" | myPt | transform ifNil:[myPt _ pt] ifNotNil:[myPt _ transform localPointToGlobal: pt]. ^super point: myPt color: c! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'DSM 10/15/1999 15:14'!drawBezier3Shape: vertices color: c borderWidth: borderWidth borderColor:borderColor self drawBezierShape: (Bezier3Segment convertBezier3ToBezier2:vertices) color: c borderWidth: borderWidth borderColor: borderColor! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:25'!drawBezierShape: vertices color: c borderWidth: borderWidth borderColor: borderColor "Draw a boundary shape that is defined by a list of vertices. Each three subsequent vertices define a quadratic bezier segment. For lines, the control point should be set to either the start or the end of the bezier curve." | fillC borderC | fillC _ self shadowColor ifNil:[c]. borderC _ self shadowColor ifNil:[borderColor]. self ensuredEngine drawBezierShape: vertices fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 11/24/1998 15:16'!drawCompressedShape: compressedShape "Draw a compressed shape" self ensuredEngine drawCompressedShape: compressedShape transform: transform.! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'DSM 10/15/1999 15:18'!drawGeneralBezier3Shape: contours color: c borderWidth: borderWidthborderColor: borderColor | b2 | b2 _ contours collect: [:b3 | Bezier3SegmentconvertBezier3ToBezier2: b3 ]. self drawGeneralBezierShape: b2 color: c borderWidth: borderWidthborderColor: borderColor! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'!drawGeneralBezierShape: contours color: c borderWidth: borderWidth borderColor: borderColor "Draw a general boundary shape (e.g., possibly containing holes)" | fillC borderC | fillC _ self shadowColor ifNil:[c]. borderC _ self shadowColor ifNil:[borderColor]. self ensuredEngine drawGeneralBezierShape: contours fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'!drawGeneralPolygon: contours color: c borderWidth: borderWidth borderColor: borderColor "Draw a general polygon (e.g., a polygon that can contain holes)" | fillC borderC | fillC _ self shadowColor ifNil:[c]. borderC _ self shadowColor ifNil:[borderColor]. self ensuredEngine drawGeneralPolygon: contours fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'!drawOval: r color: c borderWidth: borderWidth borderColor: borderColor "Draw the oval defined by the given rectangle" | fillC borderC | fillC _ self shadowColor ifNil:[c]. borderC _ self shadowColor ifNil:[borderColor]. self ensuredEngine drawOval: r fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'!drawRectangle: r color: c borderWidth: borderWidth borderColor: borderColor "Draw a rectangle" | fillC borderC | fillC _ self shadowColor ifNil:[c]. borderC _ self shadowColor ifNil:[borderColor]. self ensuredEngine drawRectangle: r fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! !!BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 5/28/2000 12:23'!render: anObject | b3d | b3d _ (B3DRenderEngine defaultForPlatformOn: form). "Install the viewport offset" b3d viewportOffset: origin. "Install the clipping rectangle for the target form" b3d clipRect: clipRect. anObject renderOn: b3d. b3d flush.! !!BalloonCanvas methodsFor: 'TODO' stamp: 'ar 2/9/1999 05:46'!line: point1 to: point2 brushForm: brush "Who's gonna use this?" | pt1 pt2 | self flush. "Sorry, but necessary..." transform ifNil:[pt1 _ point1. pt2 _ point2] ifNotNil:[pt1 _ transform localPointToGlobal: point1. pt2 _ transform localPointToGlobal: point2]. ^super line: pt1 to: pt2 brushForm: brush! !!BalloonCanvas methodsFor: 'TODO' stamp: 'ar 2/9/1999 05:46'!paragraph: para bounds: bounds color: c (self ifNoTransformWithIn: bounds) ifTrue:[^super paragraph: para bounds: bounds color: c].! !!BalloonCanvas methodsFor: 'TODO' stamp: 'ar 2/9/1999 05:38'!text: s bounds: boundsRect font: fontOrNil color: c (self ifNoTransformWithIn: boundsRect) ifTrue:[^super text: s bounds: boundsRect font: fontOrNil color: c]! !!BalloonCanvas methodsFor: 'transforming' stamp: 'ar 11/24/1998 14:45'!colorTransformBy: aColorTransform aColorTransform ifNil:[^self]. colorTransform ifNil:[colorTransform _ aColorTransform] ifNotNil:[colorTransform _ colorTransform composedWithLocal: aColorTransform]! !!BalloonCanvas methodsFor: 'transforming' stamp: 'ar 12/30/1998 10:47'!preserveStateDuring: aBlock | state result | state _ BalloonState new. state transform: transform. state colorTransform: colorTransform. state aaLevel: self aaLevel. result _ aBlock value: self. transform _ state transform. colorTransform _ state colorTransform. self aaLevel: state aaLevel. ^result! !!BalloonCanvas methodsFor: 'transforming' stamp: 'ar 11/12/1998 00:32'!transformBy: aTransform aTransform ifNil:[^self]. transform ifNil:[transform _ aTransform] ifNotNil:[transform _ transform composedWithLocal: aTransform]! !!BalloonCanvas methodsFor: 'transforming' stamp: 'ar 5/29/1999 08:59'!transformBy: aDisplayTransform during: aBlock | myTransform result | myTransform _ transform. self transformBy: aDisplayTransform. result _ aBlock value: self. transform _ myTransform. ^result! !!BalloonCanvas methodsFor: 'private' stamp: 'ar 2/9/1999 06:29'!ifNoTransformWithIn: box "Return true if the current transformation does not affect the given bounding box" | delta | "false ifFalse:[^false]." transform isNil ifTrue:[^true]. delta _ (transform localPointToGlobal: box origin) - box origin. ^(transform localPointToGlobal: box corner) - box corner = delta! !!BalloonCanvas methodsFor: 'private' stamp: 'ar 5/28/2000 12:12'!image: aForm at: aPoint sourceRect: sourceRect rule: rule | warp dstRect srcQuad dstOffset center | (self ifNoTransformWithIn: sourceRect) & false ifTrue:[^super image: aForm at: aPoint sourceRect: sourceRect rule: rule]. dstRect _ (transform localBoundsToGlobal: (aForm boundingBox translateBy: aPoint)). dstOffset _ 0@0. "dstRect origin." "dstRect _ 0@0 corner: dstRect extent." center _ 0@0."transform globalPointToLocal: dstRect origin." srcQuad _ transform globalPointsToLocal: (dstRect innerCorners). srcQuad _ srcQuad collect:[:pt| pt - aPoint]. warp _ (WarpBlt current toForm: Display) sourceForm: aForm; cellSize: 2; "installs a new colormap if cellSize > 1" combinationRule: Form over. warp copyQuad: srcQuad toRect: (dstRect translateBy: dstOffset). self frameRectangle: (aForm boundingBox translateBy: aPoint) color: Color green. "... TODO ... create a bitmap fill style from the form and use it for a simple rectangle."! !!BalloonCanvas methodsFor: 'converting' stamp: 'ar 11/11/1998 22:57'!asBalloonCanvas ^self! !!BalloonCanvas methodsFor: 'drawing-rectangles' stamp: 'ar 6/18/1999 08:48'!fillRectangle: aRectangle fillStyle: aFillStyle "Fill the given rectangle." ^self drawRectangle: aRectangle color: aFillStyle "@@: Name confusion!!!!!!" borderWidth: 0 borderColor: nil! !!BalloonCanvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:50'!fillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc "Fill the given rectangle." ^self drawOval: (aRectangle insetBy: bw // 2) color: aFillStyle "@@: Name confusion!!!!!!" borderWidth: bw borderColor: bc! !!BalloonCanvas methodsFor: 'drawing-polygons' stamp: 'ar 6/18/1999 09:00'!drawPolygon: vertices color: aColor borderWidth: bw borderColor: bc "Generalize for the BalloonCanvas" ^self drawPolygon: vertices fillStyle: aColor borderWidth: bw borderColor: bc! !!BalloonCanvas methodsFor: 'drawing-polygons' stamp: 'ar 2/17/2000 00:25'!drawPolygon: vertices fillStyle: aFillStyle borderWidth: borderWidth borderColor: borderColor "Draw a simple polygon defined by the list of vertices." | fillC borderC | fillC _ self shadowColor ifNil:[aFillStyle]. borderC _ self shadowColor ifNil:[borderColor]. self ensuredEngine drawPolygon: (vertices copyWith: vertices first) fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! !!BalloonCanvas class methodsFor: 'instance creation' stamp: 'ar 11/11/1998 19:14'!new ^super new initialize! !!BalloonDebugEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:30'!initialize super initialize. deferred _ true.! !!BalloonDebugEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 01:45'!reset workBuffer _ BalloonBuffer new: 400000. super reset.! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:04'!primClipRectInto: rect ^BalloonEnginePlugin doPrimitive:'gePrimitiveGetClipRect'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/25/1998 22:29'!primFlushNeeded "Return true if there are no more entries in AET and GET and the last scan line has been displayed" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveNeedsFlush'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:04'!primGetAALevel "Set the AA level" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetAALevel'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:04'!primGetBezierStats: statsArray ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetBezierStats'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:04'!primGetClipRect: rect ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetClipRect'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:05'!primGetCounts: statsArray ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetCounts'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:55'!primGetDepth "Set the AA level" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetDepth'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:05'!primGetFailureReason ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetFailureReason'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:05'!primGetOffset ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetOffset'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:05'!primGetTimes: statsArray ^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetTimes'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/25/1998 22:20'!primNeedsFlush "Return true if there are no more entries in AET and GET and the last scan line has been displayed" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveNeedsFlush'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:05'!primSetAALevel: level "Set the AA level" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetAALevel'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:05'!primSetClipRect: rect ^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetClipRect'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:06'!primSetColorTransform: transform ^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetColorTransform'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:06'!primSetDepth: depth ^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetDepth'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:06'!primSetEdgeTransform: transform ^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetEdgeTransform'! !!BalloonDebugEngine methodsFor: 'primitives-access' stamp: 'ar 11/24/1998 21:06'!primSetOffset: point ^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetOffset'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:11'!primAddBezierFrom: start to: end via: via leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddBezier'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:01'!primAddBezierShape: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddBezierShape'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/27/1998 14:27'!primAddBitmapFill: form colormap: cmap tile: tileFlag from: origin along: direction normal: normal xIndex: xIndex ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddBitmapFill'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:01'!primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddCompressedShape'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:02'!primAddExternalEdge: index initialX: initialX initialY: initialY initialZ: initialZ leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ^BalloonEnginePlugin doPrimitive: 'gePrimitiveRegisterExternalEdge'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:02'!primAddExternalFill: index ^BalloonEnginePlugin doPrimitive: 'gePrimitiveRegisterExternalFill'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:02'!primAddGradientFill: colorRamp from: origin along: direction normal: normal radial: isRadial ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddGradientFill'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:16'!primAddLineFrom: start to: end leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddLine'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:03'!primAddOvalFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddOval'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:03'!primAddPolygon: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddPolygon'! !!BalloonDebugEngine methodsFor: 'primitives-adding' stamp: 'ar 11/24/1998 21:20'!primAddRectFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddRect'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 20:59'!primAddActiveEdgeTableEntryFrom: edgeEntry "Add edge entry to the AET." ^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddActiveEdgeEntry'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 20:59'!primChangeActiveEdgeTableEntryFrom: edgeEntry "Change the entry in the active edge table from edgeEntry" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveChangedActiveEdgeEntry'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 20:59'!primDisplaySpanBuffer "Display the current scan line if necessary" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveDisplaySpanBuffer'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 20:59'!primFinishedProcessing "Return true if there are no more entries in AET and GET and the last scan line has been displayed" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveFinishedProcessing'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primInitializeProcessing "Initialize processing in the GE. Create the active edge table and sort it." ^BalloonEnginePlugin doPrimitive: 'gePrimitiveInitializeProcessing'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primMergeFill: fillBitmap from: fill "Merge the filled bitmap into the current output buffer." ^BalloonEnginePlugin doPrimitive: 'gePrimitiveMergeFillFrom'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primNextActiveEdgeEntryInto: edgeEntry "Store the next entry of the AET at the current y-value in edgeEntry. Return false if there is no entry, true otherwise." ^BalloonEnginePlugin doPrimitive: 'gePrimitiveNextActiveEdgeEntry'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primNextFillEntryInto: fillEntry "Store the next fill entry of the active edge table in fillEntry. Return false if there is no such entry, true otherwise" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveNextFillEntry'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primNextGlobalEdgeEntryInto: edgeEntry "Store the next entry of the GET at the current y-value in edgeEntry. Return false if there is no entry, true otherwise." ^BalloonEnginePlugin doPrimitive: 'gePrimitiveNextGlobalEdgeEntry'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primRenderImage: edge with: fill "Start/Proceed rendering the current scan line" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveRenderImage'! !!BalloonDebugEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/24/1998 21:00'!primRenderScanline: edge with: fill "Start/Proceed rendering the current scan line" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveRenderScanline'! !!BalloonDebugEngine methodsFor: 'primitives-misc' stamp: 'ar 11/24/1998 20:59'!primCopyBufferFrom: oldBuffer to: newBuffer "Copy the contents of oldBuffer into the (larger) newBuffer" ^BalloonEnginePlugin doPrimitive: 'gePrimitiveCopyBuffer'! !!BalloonDebugEngine methodsFor: 'primitives-misc' stamp: 'ar 11/24/1998 20:59'!primInitializeBuffer: buffer ^BalloonEnginePlugin doPrimitive: 'gePrimitiveInitializeBuffer'! !BalloonEdgeData defines an entry in the internal edge table of the Balloon engine.Instance Variables: index <Integer> The index into the external objects array of the associated graphics engine xValue <Integer> The computed x-value of the requested operation yValue <Integer> The y-value for the requested operation height <Integer> The (remaining) height of the edge source <Object> The object from the external objects array!!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'!index ^index! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:35'!index: anInteger index _ anInteger! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:13'!lines ^lines! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:13'!lines: anInteger ^lines _ anInteger! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'!source ^source! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 21:39'!source: anObject source _ anObject! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'!xValue ^xValue! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:35'!xValue: anInteger xValue _ anInteger! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'!yValue ^yValue! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:35'!yValue: anInteger yValue _ anInteger! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 19:56'!zValue ^zValue! !!BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 19:56'!zValue: anInteger zValue _ anInteger! !!BalloonEdgeData methodsFor: 'computing' stamp: 'ar 10/27/1998 15:53'!stepToFirstScanLine source stepToFirstScanLineAt: yValue in: self! !!BalloonEdgeData methodsFor: 'computing' stamp: 'ar 10/27/1998 15:53'!stepToNextScanLine source stepToNextScanLineAt: yValue in: self! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:29'!flush "Force all pending primitives onscreen" workBuffer ifNil:[^self]. self copyBits. self release.! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 12/30/1998 11:24'!initialize externals _ OrderedCollection new: 100. span _ Bitmap new: 2048. bitBlt _ nil. self bitBlt: ((BitBlt toForm: Display) destRect: Display boundingBox; yourself). forms _ #(). deferred _ false.! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:42'!postFlushIfNeeded "Force all pending primitives onscreen" workBuffer ifNil:[^self]. (deferred not or:[postFlushNeeded]) ifTrue:[ self copyBits. self release].! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:43'!preFlushIfNeeded "Force all pending primitives onscreen" workBuffer ifNil:[^self]. self primFlushNeeded ifTrue:[ self copyBits. self reset].! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/11/1998 22:52'!release self class recycleBuffer: workBuffer. workBuffer _ nil.! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:34'!reset workBuffer ifNil:[workBuffer _ self class allocateOrRecycleBuffer: 10000]. self primInitializeBuffer: workBuffer. self primSetAALevel: self aaLevel. self primSetOffset: destOffset. self primSetClipRect: clipRect. self primSetEdgeTransform: edgeTransform. self primSetColorTransform: colorTransform. forms _ #().! !!BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:39'!resetIfNeeded workBuffer ifNil:[self reset]. self primSetEdgeTransform: edgeTransform. self primSetColorTransform: colorTransform. self primSetDepth: self primGetDepth + 1. postFlushNeeded _ false.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 10/11/1999 16:49'!drawBezierShape: points fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills _ self registerFill: fillStyle and: borderFill. self primAddBezierShape: points segments: (points size) // 3 fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:44'!drawCompressedShape: shape transform: aTransform | fillIndexList | self edgeTransform: aTransform. self resetIfNeeded. fillIndexList _ self registerFills: shape fillStyles. self primAddCompressedShape: shape points segments: shape numSegments leftFills: shape leftFills rightFills: shape rightFills lineWidths: shape lineWidths lineFills: shape lineFills fillIndexList: fillIndexList. self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 1/15/1999 03:02'!drawGeneralBezierShape: contours fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills _ self registerFill: fillStyle and: borderFill. contours do:[:points| self primAddBezierShape: points segments: (points size // 3) fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). "Note: To avoid premature flushing of the pipeline we need to reset the flush bit within the engine." self primFlushNeeded: false. ]. "And set the flush bit afterwards" self primFlushNeeded: true. self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 1/15/1999 03:02'!drawGeneralPolygon: contours fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills _ self registerFill: fillStyle and: borderFill. contours do:[:points| self primAddPolygon: points segments: points size fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). "Note: To avoid premature flushing of the pipeline we need to reset the flush bit within the engine." self primFlushNeeded: false. ]. "And set the flush bit afterwards" self primFlushNeeded: true. self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'!drawOval: rect fill: fillStyle borderWidth: borderWidth borderColor: borderColor transform: aMatrix | fills | self edgeTransform: aMatrix. self resetIfNeeded. fills _ self registerFill: fillStyle and: borderColor. self primAddOvalFrom: rect origin to: rect corner fillIndex: (fills at: 1) borderWidth: borderWidth borderColor: (fills at: 2). self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'!drawPolygon: points fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills _ self registerFill: fillStyle and: borderFill. self primAddPolygon: points segments: points size fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'!drawRectangle: rect fill: fillStyle borderWidth: borderWidth borderColor: borderColor transform: aMatrix | fills | self edgeTransform: aMatrix. self resetIfNeeded. fills _ self registerFill: fillStyle and: borderColor. self primAddRectFrom: rect origin to: rect corner fillIndex: (fills at: 1) borderWidth: borderWidth borderColor: (fills at: 2). self postFlushIfNeeded.! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 1/14/1999 15:24'!registerFill: aFillStyle "Register the given fill style." | theForm | aFillStyle ifNil:[^0]. aFillStyle isSolidFill ifTrue:[^aFillStyle scaledPixelValue32]. aFillStyle isGradientFill ifTrue:[ ^self primAddGradientFill: aFillStyle pixelRamp from: aFillStyle origin along: aFillStyle direction normal: aFillStyle normal radial: aFillStyle isRadialFill ]. aFillStyle isBitmapFill ifTrue:[ theForm _ aFillStyle form. theForm unhibernate. forms _ forms copyWith: theForm. ^self primAddBitmapFill: theForm colormap: (theForm colormapIfNeededForDepth: 32) tile: aFillStyle isTiled from: aFillStyle origin along: aFillStyle direction normal: aFillStyle normal xIndex: forms size]. ^0! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'!registerFill: fill1 and: fill2 ^self registerFills: (Array with: fill1 with: fill2)! !!BalloonEngine methodsFor: 'drawing' stamp: 'ar 1/14/1999 15:24'!registerFill: aFillStyle transform: aTransform aFillStyle ifNil:[^0]. aFillStyle isSolidFill ifTrue:[^aFillStyle scaledPixelValue32]. aFillStyle isGradientFill ifTrue:[ ^self primAddGradientFill: aFillStyle pixelRamp from: aFillStyle origin along: aFillStyle direction normal: aFillStyle normal radial: aFillStyle isRadialFill matrix: aTransform. ]. ^0! !!BalloonEngine methodsFor: 'drawing' stamp: 'di 11/21/1999 20:15'!registerFills: fills | fillIndexList index fillIndex | ((colorTransform notNil and:[colorTransform isAlphaTransform]) or:[ fills anySatisfy: [:any| any notNil and:[any isTranslucent]]]) ifTrue:[ self flush. self reset. postFlushNeeded _ true]. fillIndexList _ WordArray new: fills size. index _ 1. [index <= fills size] whileTrue:[ fillIndex _ self registerFill: (fills at: index). fillIndex == nil ifTrue:[index _ 1] "Need to start over" ifFalse:[fillIndexList at: index put: fillIndex. index _ index+1] ]. ^fillIndexList! !!BalloonEngine methodsFor: 'copying' stamp: 'ar 11/25/1998 00:45'!canProceedAfter: failureReason "Check if we can proceed after the failureReason indicated." | newBuffer | failureReason = GErrorNeedFlush ifTrue:[ "Need to flush engine before proceeding" self copyBits. self reset. ^true]. failureReason = GErrorNoMoreSpace ifTrue:[ "Work buffer is too small" newBuffer _ workBuffer species new: workBuffer size * 2. self primCopyBufferFrom: workBuffer to: newBuffer. workBuffer _ newBuffer. ^true]. "Not handled" ^false! !!BalloonEngine methodsFor: 'copying' stamp: 'ar 11/29/1998 18:22'!copyBits self copyLoopFaster.! !!BalloonEngine methodsFor: 'copying' stamp: 'ar 11/14/1998 19:32'!copyLoop "This is the basic rendering loop using as little primitive support as possible." | finished edge fill | edge _ BalloonEdgeData new. fill _ BalloonFillData new. self primInitializeProcessing. "Initialize the GE for processing" [self primFinishedProcessing] whileFalse:[ "Step 1: Process the edges in the global edge table that will be added in this step" [finished _ self primNextGlobalEdgeEntryInto: edge. finished] whileFalse:[ edge source: (externals at: edge index). edge stepToFirstScanLine. self primAddActiveEdgeTableEntryFrom: edge]. "Step 2: Scan the active edge table" [finished _ self primNextFillEntryInto: fill. finished] whileFalse:[ fill source: (externals at: fill index). "Compute the new fill" fill computeFill. "And mix it in the out buffer" self primMergeFill: fill destForm bits from: fill]. "Step 3: Display the current span buffer if necessary" self primDisplaySpanBuffer. "Step 4: Advance and resort the active edge table" [finished _ self primNextActiveEdgeEntryInto: edge. finished] whileFalse:[ "If the index is zero then the edge has been handled by the GE" edge source: (externals at: edge index). edge stepToNextScanLine. self primChangeActiveEdgeTableEntryFrom: edge]. ]. self primGetTimes: Times. self primGetCounts: Counts. self primGetBezierStats: BezierStats.! !!BalloonEngine methodsFor: 'copying' stamp: 'ar 11/14/1998 19:32'!copyLoopFaster "This is a copy loop drawing one scan line at a time" | edge fill reason | edge _ BalloonEdgeData new. fill _ BalloonFillData new. [self primFinishedProcessing] whileFalse:[ reason _ self primRenderScanline: edge with: fill. "reason ~= 0 means there has been a problem" reason = 0 ifFalse:[ self processStopReason: reason edge: edge fill: fill. ]. ]. self primGetTimes: Times. self primGetCounts: Counts. self primGetBezierStats: BezierStats.! !!BalloonEngine methodsFor: 'copying' stamp: 'ar 11/14/1998 19:33'!copyLoopFastest "This is a copy loop drawing the entire image" | edge fill reason | edge _ BalloonEdgeData new. fill _ BalloonFillData new. [self primFinishedProcessing] whileFalse:[ reason _ self primRenderImage: edge with: fill. "reason ~= 0 means there has been a problem" reason = 0 ifFalse:[ self processStopReason: reason edge: edge fill: fill. ]. ]. self primGetTimes: Times. self primGetCounts: Counts. self primGetBezierStats: BezierStats.! !!BalloonEngine methodsFor: 'copying' stamp: 'ar 11/11/1998 21:19'!processStopReason: reason edge: edge fill: fill "The engine has stopped because of some reason. Try to figure out how to respond and do the necessary actions." "Note: The order of operations below can affect the speed" "Process unknown fills first" reason = GErrorFillEntry ifTrue:[ fill source: (externals at: fill index). "Compute the new fill" fill computeFill. "And mix it in the out buffer" ^self primMergeFill: fill destForm bits from: fill]. "Process unknown steppings in the AET second" reason = GErrorAETEntry ifTrue:[ edge source: (externals at: edge index). edge stepToNextScanLine. ^self primChangeActiveEdgeTableEntryFrom: edge]. "Process unknown entries in the GET third" reason = GErrorGETEntry ifTrue:[ edge source: (externals at: edge index). edge stepToFirstScanLine. ^self primAddActiveEdgeTableEntryFrom: edge]. "Process generic problems last" (self canProceedAfter: reason) ifTrue:[^self]. "Okay." ^self error:'Unkown stop reason in graphics engine'! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/11/1998 23:04'!aaLevel ^aaLevel ifNil:[1]! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/11/1998 23:04'!aaLevel: anInteger aaLevel _ (anInteger min: 4) max: 1.! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/29/1998 01:51'!aaTransform "Return a transformation for the current anti-aliasing level" | matrix | matrix _ MatrixTransform2x3 withScale: (self aaLevel) asFloat asPoint. matrix offset: (self aaLevel // 2) asFloat asPoint. ^matrix composedWith:(MatrixTransform2x3 withOffset: destOffset asFloatPoint)! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/13/1998 03:04'!bitBlt ^bitBlt! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 5/28/2000 15:02'!bitBlt: aBitBlt bitBlt _ aBitBlt. bitBlt isNil ifTrue:[^self]. self class primitiveSetBitBltPlugin: bitBlt getPluginName. self clipRect: bitBlt clipRect. bitBlt sourceForm: (Form extent: span size @ 1 depth: 32 bits: span); sourceRect: (0@0 extent: 1@span size); colorMap: (Color colorMapIfNeededFrom: 32 to: bitBlt destForm depth); combinationRule: (bitBlt destForm depth >= 8 ifTrue:[34] ifFalse:[Form paint]).! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/1/1998 02:57'!clipRect ^clipRect! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/13/1998 02:44'!clipRect: aRect clipRect _ aRect truncated! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/24/1998 15:04'!colorTransform ^colorTransform! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/24/1998 15:04'!colorTransform: aColorTransform colorTransform _ aColorTransform! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 12/30/1998 11:24'!deferred ^deferred! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 12/30/1998 11:24'!deferred: aBoolean deferred _ aBoolean.! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/1/1998 02:56'!destOffset ^destOffset! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/12/1998 00:22'!destOffset: aPoint destOffset _ aPoint asIntegerPoint. bitBlt destX: aPoint x; destY: aPoint y.! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/25/1998 22:34'!edgeTransform ^edgeTransform! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/25/1998 22:34'!edgeTransform: aTransform edgeTransform _ aTransform.! !!BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/29/1998 01:51'!fullTransformFrom: aMatrix | m | m _ self aaTransform composedWith: aMatrix. "m offset: m offset + destOffset." ^m! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primClipRectInto: rect <primitive: 'gePrimitiveGetClipRect'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive:'gePrimitiveGetClipRect']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/26/1998 19:46'!primFlushNeeded <primitive:'gePrimitiveNeedsFlush'> ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 1/15/1999 03:03'!primFlushNeeded: aBoolean <primitive:'gePrimitiveNeedsFlushPut'> ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetAALevel "Set the AA level" <primitive: 'gePrimitiveGetAALevel'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetAALevel']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetBezierStats: statsArray <primitive:'gePrimitiveGetBezierStats'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetBezierStats']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetClipRect: rect <primitive: 'gePrimitiveGetClipRect'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetClipRect']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetCounts: statsArray <primitive:'gePrimitiveGetCounts'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetCounts']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/26/1998 19:46'!primGetDepth <primitive:'gePrimitiveGetDepth'> ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetFailureReason <primitive: 'gePrimitiveGetFailureReason'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetFailureReason']. ^0! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetOffset <primitive: 'gePrimitiveGetOffset'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetOffset']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primGetTimes: statsArray <primitive:'gePrimitiveGetTimes'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveGetTimes']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primSetAALevel: level "Set the AA level" <primitive: 'gePrimitiveSetAALevel'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetAALevel']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primSetClipRect: rect <primitive: 'gePrimitiveSetClipRect'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetClipRect']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/26/1998 19:47'!primSetColorTransform: transform <primitive:'gePrimitiveSetColorTransform'> ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/26/1998 19:47'!primSetDepth: depth <primitive:'gePrimitiveSetDepth'> ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/26/1998 19:47'!primSetEdgeTransform: transform <primitive:'gePrimitiveSetEdgeTransform'> ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 11/11/1998 21:55'!primSetOffset: point <primitive: 'gePrimitiveSetOffset'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveSetOffset']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:53'!primAddBezierFrom: start to: end via: via leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex <primitive: 'gePrimitiveAddBezier'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddBezierFrom: start to: end via: via leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:53'!primAddBezierShape: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill <primitive: 'gePrimitiveAddBezierShape'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddBezierShape: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/27/1998 14:27'!primAddBitmapFill: form colormap: cmap tile: tileFlag from: origin along: direction normal: normal xIndex: xIndex <primitive: 'gePrimitiveAddBitmapFill'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddBitmapFill: form colormap: cmap tile: tileFlag from: origin along: direction normal: normal xIndex: xIndex ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:53'!primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList <primitive: 'gePrimitiveAddCompressedShape'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:53'!primAddExternalEdge: index initialX: initialX initialY: initialY initialZ: initialZ leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex <primitive: 'gePrimitiveRegisterExternalEdge'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddExternalEdge: index initialX: initialX initialY: initialY initialZ: initialZ leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:53'!primAddExternalFill: index <primitive: 'gePrimitiveRegisterExternalFill'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddExternalFill: index ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:53'!primAddGradientFill: colorRamp from: origin along: direction normal: normal radial: isRadial <primitive: 'gePrimitiveAddGradientFill'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddGradientFill: colorRamp from: origin along: direction normal: normal radial: isRadial ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:52'!primAddLineFrom: start to: end leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex <primitive: 'gePrimitiveAddLine'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddLineFrom: start to: end leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:51'!primAddOvalFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 <primitive: 'gePrimitiveAddOval'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddOvalFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 11/26/1998 19:52'!primAddPolygon: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill <primitive: 'gePrimitiveAddPolygon'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddPolygon: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 1/14/1999 15:37'!primAddRectFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 <primitive: 'gePrimitiveAddRect'> (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddRectFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/14/1998 20:47'!primAddActiveEdgeTableEntryFrom: edgeEntry "Add edge entry to the AET." <primitive: 'gePrimitiveAddActiveEdgeEntry'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveAddActiveEdgeEntry']. (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddActiveEdgeTableEntryFrom: edgeEntry ]. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:56'!primChangeActiveEdgeTableEntryFrom: edgeEntry "Change the entry in the active edge table from edgeEntry" <primitive: 'gePrimitiveChangedActiveEdgeEntry'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveChangedActiveEdgeEntry']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primDisplaySpanBuffer "Display the current scan line if necessary" <primitive: 'gePrimitiveDisplaySpanBuffer'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveDisplaySpanBuffer']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primFinishedProcessing "Return true if there are no more entries in AET and GET and the last scan line has been displayed" <primitive: 'gePrimitiveFinishedProcessing'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveFinishedProcessing']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primInitializeProcessing "Initialize processing in the GE. Create the active edge table and sort it." <primitive: 'gePrimitiveInitializeProcessing'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveInitializeProcessing']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primMergeFill: fillBitmap from: fill "Merge the filled bitmap into the current output buffer." <primitive: 'gePrimitiveMergeFillFrom'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveMergeFillFrom']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primNextActiveEdgeEntryInto: edgeEntry "Store the next entry of the AET at the current y-value in edgeEntry. Return false if there is no entry, true otherwise." <primitive: 'gePrimitiveNextActiveEdgeEntry'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveNextActiveEdgeEntry']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primNextFillEntryInto: fillEntry "Store the next fill entry of the active edge table in fillEntry. Return false if there is no such entry, true otherwise" <primitive: 'gePrimitiveNextFillEntry'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveNextFillEntry']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:56'!primNextGlobalEdgeEntryInto: edgeEntry "Store the next entry of the GET at the current y-value in edgeEntry. Return false if there is no entry, true otherwise." <primitive: 'gePrimitiveNextGlobalEdgeEntry'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveNextGlobalEdgeEntry']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primRenderImage: edge with: fill "Start/Proceed rendering the current scan line" <primitive: 'gePrimitiveRenderImage'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveRenderImage']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 11/11/1998 21:55'!primRenderScanline: edge with: fill "Start/Proceed rendering the current scan line" <primitive: 'gePrimitiveRenderScanline'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveRenderScanline']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-misc' stamp: 'ar 11/11/1998 21:55'!primCopyBufferFrom: oldBuffer to: newBuffer "Copy the contents of oldBuffer into the (larger) newBuffer" <primitive: 'gePrimitiveCopyBuffer'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveCopyBuffer']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'primitives-misc' stamp: 'ar 11/11/1998 21:55'!primInitializeBuffer: buffer <primitive: 'gePrimitiveInitializeBuffer'> Debug ifTrue:[^BalloonEnginePlugin doPrimitive: 'gePrimitiveInitializeBuffer']. ^self primitiveFailed! !!BalloonEngine methodsFor: 'experimental' stamp: 'ar 11/12/1998 19:53'!registerBezier: aCurve transformation: aMatrix self primAddBezierFrom: aCurve start to: aCurve end via: aCurve via leftFillIndex: (self registerFill: aCurve leftFill transform: aMatrix) rightFillIndex: (self registerFill: aCurve rightFill transform: aMatrix) matrix: aMatrix! !!BalloonEngine methodsFor: 'experimental' stamp: 'ar 11/11/1998 21:15'!registerBoundary: boundaryObject transformation: aMatrix | external | external _ boundaryObject asEdgeRepresentation: (self fullTransformFrom: aMatrix). self subdivideExternalEdge: external from: boundaryObject.! !!BalloonEngine methodsFor: 'experimental' stamp: 'ar 11/12/1998 19:54'!registerExternalEdge: externalEdge from: boundaryObject externals addLast: externalEdge. self primAddExternalEdge: externals size initialX: externalEdge initialX initialY: externalEdge initialY initialZ: externalEdge initialZ leftFillIndex: (self registerFill: boundaryObject leftFill transform: nil) rightFillIndex: (self registerFill: boundaryObject rightFill transform: nil)! !!BalloonEngine methodsFor: 'experimental' stamp: 'ar 11/12/1998 19:54'!registerLine: aLine transformation: aMatrix self primAddLineFrom: aLine start to: aLine end leftFillIndex: (self registerFill: aLine leftFill transform: aMatrix) rightFillIndex: (self registerFill: aLine rightFill transform: aMatrix) matrix: aMatrix! !!BalloonEngine methodsFor: 'experimental' stamp: 'ar 11/11/1998 21:15'!subdivideExternalEdge: external from: boundaryObject | external2 | external2 _ external subdivide. external2 notNil ifTrue:[ self subdivideExternalEdge: external from: boundaryObject. self subdivideExternalEdge: external2 from: boundaryObject. ] ifFalse:[ self registerExternalEdge: external from: boundaryObject. ].! !!BalloonEngine methodsFor: 'profiling' stamp: 'ar 11/11/1998 21:16'!doAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList matrix: aMatrix "Note: This method is for profiling the overhead of loading a compressed shape into the engine." ^self primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList matrix: aMatrix! !!BalloonEngine class methodsFor: 'instance creation' stamp: 'ar 10/9/1998 21:44'!new ^super new initialize! !!BalloonEngine class methodsFor: 'class initialization' stamp: 'ar 11/11/1998 22:49'!initialize "BalloonEngine initialize" BufferCache _ WeakArray new: 1. Smalltalk garbageCollect. "Make the cache old" CacheProtect _ Semaphore forMutualExclusion. Times _ WordArray new: 10. Counts _ WordArray new: 10. BezierStats _ WordArray new: 4. Debug ifNil:[Debug _ false].! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/25/1998 17:37'!debug: aBoolean "BalloonEngine debug: true" "BalloonEngine debug: false" Debug _ aBoolean! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 1/12/1999 11:17'!doProfileStats: aBool "Note: On Macintosh systems turning on profiling can significantly degrade the performance of Balloon since we're using the high accuracy timer for measuring." "BalloonEngine doProfileStats: true" "BalloonEngine doProfileStats: false" <primitive: 'gePrimitiveDoProfileStats'> ^false! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57'!printBezierStats "BalloonEngine printBezierStats" "BalloonEngine resetBezierStats" Transcript cr; nextPutAll:'Bezier statistics:'; crtab; print: (BezierStats at: 1); tab; nextPutAll:' non-monoton curves splitted'; crtab; print: (BezierStats at: 2); tab; nextPutAll:' curves splitted for numerical accuracy'; crtab; print: (BezierStats at: 3); tab; nextPutAll:' curves splitted to avoid integer overflow'; crtab; print: (BezierStats at: 4); tab; nextPutAll:' curves internally converted to lines'; endEntry.! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:59'!printStat: time count: n string: aString Transcript cr; print: time; tab; nextPutAll:' mSecs -- '; print: n; tab; nextPutAll:' ops -- '; print: ((time asFloat / (n max: 1) asFloat) roundTo: 0.01); tab; nextPutAll: ' avg. mSecs/op -- '; nextPutAll: aString.! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 1/12/1999 10:52'!printStats "BalloonEngine doProfileStats: true" "BalloonEngine printStats" "BalloonEngine resetStats" Transcript cr; nextPutAll:'/************** BalloonEngine statistics ****************/'. self printStat: (Times at: 1) count: (Counts at: 1) string: 'Initialization'. self printStat: (Times at: 2) count: (Counts at: 2) string: 'Finish test'. self printStat: (Times at: 3) count: (Counts at: 3) string: 'Fetching/Adding GET entries'. self printStat: (Times at: 4) count: (Counts at: 4) string: 'Adding AET entries'. self printStat: (Times at: 5) count: (Counts at: 5) string: 'Fetching/Computing fills'. self printStat: (Times at: 6) count: (Counts at: 6) string: 'Merging fills'. self printStat: (Times at: 7) count: (Counts at: 7) string: 'Displaying span buffer'. self printStat: (Times at: 8) count: (Counts at: 8) string: 'Fetching/Updating AET entries'. self printStat: (Times at: 9) count: (Counts at: 9) string: 'Changing AET entries'. Transcript cr; print: Times sum; nextPutAll:' mSecs for all operations'. Transcript cr; print: Counts sum; nextPutAll: ' overall operations'. Transcript endEntry.! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57'!resetBezierStats BezierStats _ WordArray new: 4.! !!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:38'!resetStats Times _ WordArray new: 10. Counts _ WordArray new: 10.! !!BalloonEngine class methodsFor: 'private' stamp: 'ar 11/11/1998 22:50'!allocateOrRecycleBuffer: initialSize "Try to recycly a buffer. If this is not possibly, create a new one." | buffer | CacheProtect critical:[ buffer _ BufferCache at: 1. BufferCache at: 1 put: nil. ]. ^buffer ifNil:[BalloonBuffer new: initialSize]! !!BalloonEngine class methodsFor: 'private' stamp: 'ar 5/28/2000 22:17'!primitiveSetBitBltPlugin: pluginName <primitive: 'primitiveSetBitBltPlugin' module: 'B2DPlugin'> ^nil! !!BalloonEngine class methodsFor: 'private' stamp: 'ar 11/11/1998 22:51'!recycleBuffer: balloonBuffer "Try to keep the buffer for later drawing operations." | buffer | CacheProtect critical:[ buffer _ BufferCache at: 1. (buffer isNil or:[buffer size < balloonBuffer size] ) ifTrue:[BufferCache at: 1 put: balloonBuffer]. ].! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:34'!aaColorMaskGet ^workBuffer at: GWAAColorMask! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:34'!aaColorMaskPut: value ^workBuffer at: GWAAColorMask put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:34'!aaColorShiftGet ^workBuffer at: GWAAColorShift! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:34'!aaColorShiftPut: value ^workBuffer at: GWAAColorShift put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:34'!aaHalfPixelGet ^workBuffer at: GWAAHalfPixel! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:35'!aaHalfPixelPut: value ^workBuffer at: GWAAHalfPixel put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:35'!aaLevelGet ^workBuffer at: GWAALevel! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:35'!aaLevelPut: value ^workBuffer at: GWAALevel put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:35'!aaScanMaskGet ^workBuffer at: GWAAScanMask! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:35'!aaScanMaskPut: value ^workBuffer at: GWAAScanMask put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:35'!aaShiftGet ^workBuffer at: GWAAShift! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 00:36'!aaShiftPut: value ^workBuffer at: GWAAShift put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!aetStartGet ^workBuffer at: GWAETStart! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:29'!aetStartPut: value ^workBuffer at: GWAETStart put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!aetUsedGet ^workBuffer at: GWAETUsed! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:29'!aetUsedPut: value ^workBuffer at: GWAETUsed put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 00:43'!clearSpanBufferGet ^workBuffer at: GWClearSpanBuffer! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 00:44'!clearSpanBufferPut: value ^workBuffer at: GWClearSpanBuffer put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:46'!clipMaxXGet ^workBuffer at: GWClipMaxX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:46'!clipMaxXPut: value ^workBuffer at: GWClipMaxX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:46'!clipMaxYGet ^workBuffer at: GWClipMaxY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:46'!clipMaxYPut: value ^workBuffer at: GWClipMaxY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:46'!clipMinXGet ^workBuffer at: GWClipMinX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:47'!clipMinXPut: value ^workBuffer at: GWClipMinX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:47'!clipMinYGet ^workBuffer at: GWClipMinY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 18:47'!clipMinYPut: value ^workBuffer at: GWClipMinY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 21:36'!colorTransform self returnTypeC:'float *'. ^self cCoerce: workBuffer + GWColorTransform to:'float *'! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!currentYGet ^workBuffer at: GWCurrentY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 21:27'!currentYPut: value ^workBuffer at: GWCurrentY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 20:28'!currentZGet ^workBuffer at: GWCurrentZ! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 20:29'!currentZPut: value ^workBuffer at: GWCurrentZ put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 16:23'!destOffsetXGet ^workBuffer at: GWDestOffsetX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 16:24'!destOffsetXPut: value ^workBuffer at: GWDestOffsetX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 16:23'!destOffsetYGet ^workBuffer at: GWDestOffsetY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 16:24'!destOffsetYPut: value ^workBuffer at: GWDestOffsetY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 21:36'!edgeTransform self returnTypeC:'float *'. ^self cCoerce: workBuffer + GWEdgeTransform to:'float *'! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!fillMaxXGet ^workBuffer at: GWFillMaxX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:29'!fillMaxXPut: value ^workBuffer at: GWFillMaxX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!fillMaxYGet ^workBuffer at: GWFillMaxY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:30'!fillMaxYPut: value ^workBuffer at: GWFillMaxY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!fillMinXGet ^workBuffer at: GWFillMinX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:30'!fillMinXPut: value ^workBuffer at: GWFillMinX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!fillMinYGet ^workBuffer at: GWFillMinY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:30'!fillMinYPut: value ^workBuffer at: GWFillMinY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!fillOffsetXGet ^workBuffer at: GWFillOffsetX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:30'!fillOffsetXPut: value ^workBuffer at: GWFillOffsetX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!fillOffsetYGet ^workBuffer at: GWFillOffsetY! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:30'!fillOffsetYPut: value ^workBuffer at: GWFillOffsetY put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 17:08'!firstPointListGet ^workBuffer at: GWPointListFirst! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/29/1998 17:08'!firstPointListPut: value ^workBuffer at: GWPointListFirst put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!getStartGet ^workBuffer at: GWGETStart! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:30'!getStartPut: value ^workBuffer at: GWGETStart put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:27'!getUsedGet ^workBuffer at: GWGETUsed! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!getUsedPut: value ^workBuffer at: GWGETUsed put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 21:36'!hasColorTransformGet ^workBuffer at: GWHasColorTransform! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 21:36'!hasColorTransformPut: value ^workBuffer at: GWHasColorTransform put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 21:36'!hasEdgeTransformGet ^workBuffer at: GWHasEdgeTransform! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/24/1998 21:35'!hasEdgeTransformPut: value ^workBuffer at: GWHasEdgeTransform put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/9/1998 15:36'!incrementStat: statIndex by: value ^workBuffer at: statIndex put: (workBuffer at: statIndex) + value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!lastExportedEdgeGet ^workBuffer at: GWLastExportedEdge! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 20:11'!lastExportedEdgePut: value ^workBuffer at: GWLastExportedEdge put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 14:24'!lastExportedFillGet ^workBuffer at: GWLastExportedFill! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 14:24'!lastExportedFillPut: value ^workBuffer at: GWLastExportedFill put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:51'!lastExportedLeftXGet ^workBuffer at: GWLastExportedLeftX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:51'!lastExportedLeftXPut: value ^workBuffer at: GWLastExportedLeftX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:51'!lastExportedRightXGet ^workBuffer at: GWLastExportedRightX! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:51'!lastExportedRightXPut: value ^workBuffer at: GWLastExportedRightX put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!magicNumberGet ^workBuffer at: GWMagicIndex! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:39'!magicNumberPut: value ^workBuffer at: GWMagicIndex put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/25/1998 00:20'!needsFlushGet ^workBuffer at: GWNeedsFlush! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/25/1998 00:20'!needsFlushPut: value ^workBuffer at: GWNeedsFlush put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!objStartGet ^workBuffer at: GWObjStart! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:32'!objStartPut: value ^workBuffer at: GWObjStart put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!objUsedGet ^workBuffer at: GWObjUsed! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:32'!objUsedPut: value ^workBuffer at: GWObjUsed put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:33'!point1Get self returnTypeC:'int *'. ^self cCoerce: workBuffer + GWPoint1 to:'int *'! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:34'!point2Get self returnTypeC:'int *'. ^self cCoerce: workBuffer + GWPoint2 to:'int *'! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/28/1998 16:34'!point3Get self returnTypeC:'int *'. ^self cCoerce: workBuffer + GWPoint3 to:'int *'! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 11/1/1998 03:13'!point4Get self returnTypeC:'int *'. ^self cCoerce: workBuffer + GWPoint4 to:'int *'! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!spanEndAAGet ^workBuffer at: GWSpanEndAA! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!spanEndAAPut: value ^workBuffer at: GWSpanEndAA put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!spanEndGet ^workBuffer at: GWSpanEnd! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!spanEndPut: value ^workBuffer at: GWSpanEnd put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!spanSizeGet ^workBuffer at: GWSpanSize! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!spanSizePut: value ^workBuffer at: GWSpanSize put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!spanStartGet ^workBuffer at: GWSpanStart! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!spanStartPut: value ^workBuffer at: GWSpanStart put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!stateGet ^workBuffer at: GWState! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!statePut: value ^workBuffer at: GWState put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!stopReasonGet ^workBuffer at: GWStopReason! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:31'!stopReasonPut: value ^workBuffer at: GWStopReason put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:28'!wbSizeGet ^workBuffer at: GWSize! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:37'!wbSizePut: value ^workBuffer at: GWSize put: value! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 23:29'!wbTopGet ^workBuffer at: GWBufferTop! !!BalloonEngineBase methodsFor: 'accessing state' stamp: 'ar 10/27/1998 18:32'!wbTopPut: value ^workBuffer at: GWBufferTop put: value! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:22'!obj: object at: index ^objBuffer at: object + index! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:22'!obj: object at: index put: value ^objBuffer at: object + index put: value! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:02'!objectHeaderOf: obj ^self makeUnsignedFrom:(self obj: obj at: GEObjectType)! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:03'!objectIndexOf: obj ^self obj: obj at: GEObjectIndex! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:03'!objectIndexOf: obj put: value ^self obj: obj at: GEObjectIndex put: value! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:03'!objectLengthOf: obj ^self obj: obj at: GEObjectLength! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:03'!objectLengthOf: obj put: value ^self obj: obj at: GEObjectLength put: value! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:03'!objectTypeOf: obj ^(self makeUnsignedFrom:(self obj: obj at: GEObjectType)) bitAnd: GEPrimitiveTypeMask! !!BalloonEngineBase methodsFor: 'accessing objects' stamp: 'ar 11/24/1998 22:03'!objectTypeOf: obj put: value ^self obj: obj at: GEObjectType put: value! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/9/1998 15:35'!edgeFillsInvalidate: edge ^self objectTypeOf: edge put: ((self objectTypeOf: edge) bitOr: GEEdgeFillsInvalid)! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/9/1998 15:35'!edgeFillsValidate: edge ^self objectTypeOf: edge put: ((self objectTypeOf: edge) bitAnd: GEEdgeFillsInvalid bitInvert32)! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:04'!edgeLeftFillOf: edge ^self obj: edge at: GEFillIndexLeft! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:04'!edgeLeftFillOf: edge put: value ^self obj: edge at: GEFillIndexLeft put: value! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:04'!edgeNumLinesOf: edge ^self obj: edge at: GENumLines! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:04'!edgeNumLinesOf: edge put: value ^self obj: edge at: GENumLines put: value! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:05'!edgeRightFillOf: edge ^self obj: edge at: GEFillIndexRight! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:05'!edgeRightFillOf: edge put: value ^self obj: edge at: GEFillIndexRight put: value! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/9/1998 15:35'!edgeTypeOf: edge "Return the edge type (e.g., witout the wide edge flag)" ^(self objectTypeOf: edge) >> 1! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:05'!edgeXValueOf: edge ^self obj: edge at: GEXValue! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:05'!edgeXValueOf: edge put: value ^self obj: edge at: GEXValue put: value! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:05'!edgeYValueOf: edge ^self obj: edge at: GEYValue! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:06'!edgeYValueOf: edge put: value ^self obj: edge at: GEYValue put: value! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:06'!edgeZValueOf: edge ^self obj: edge at: GEZValue! !!BalloonEngineBase methodsFor: 'accessing edges' stamp: 'ar 11/24/1998 22:06'!edgeZValueOf: edge put: value ^self obj: edge at: GEZValue put: value! !!BalloonEngineBase methodsFor: 'accessing stack' stamp: 'ar 10/31/1998 00:43'!wbStackClear self wbTopPut: self wbSizeGet.! !!BalloonEngineBase methodsFor: 'accessing stack' stamp: 'ar 11/9/1998 15:34'!wbStackPop: nItems self wbTopPut: self wbTopGet + nItems.! !!BalloonEngineBase methodsFor: 'accessing stack' stamp: 'ar 10/30/1998 17:16'!wbStackPush: nItems (self allocateStackEntry: nItems) ifFalse:[^false]. self wbTopPut: self wbTopGet - nItems. ^true! !!BalloonEngineBase methodsFor: 'accessing stack' stamp: 'ar 10/30/1998 17:17'!wbStackSize ^self wbSizeGet - self wbTopGet! !!BalloonEngineBase methodsFor: 'accessing stack' stamp: 'ar 11/9/1998 15:34'!wbStackValue: index ^workBuffer at: self wbTopGet + index! !!BalloonEngineBase methodsFor: 'accessing stack' stamp: 'ar 11/9/1998 15:34'!wbStackValue: index put: value ^workBuffer at: self wbTopGet + index put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/7/1998 22:25'!fillTypeOf: fill ^((self objectTypeOf: fill) bitAnd: GEPrimitiveFillMask) >> 8! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:08'!stackFillDepth: index ^self wbStackValue: index+1! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:08'!stackFillDepth: index put: value ^self wbStackValue: index+1 put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/25/1998 14:31'!stackFillEntryLength ^3! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/25/1998 14:35'!stackFillRightX: index ^self wbStackValue: index+2! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/25/1998 14:35'!stackFillRightX: index put: value ^self wbStackValue: index+2 put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:10'!stackFillSize ^self wbStackSize! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:09'!stackFillValue: index ^self wbStackValue: index! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:09'!stackFillValue: index put: value ^self wbStackValue: index put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/24/1998 22:49'!topDepth self stackFillSize = 0 ifTrue:[^-1] ifFalse:[^self topFillDepth].! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:28'!topFill self stackFillSize = 0 ifTrue:[^0] ifFalse:[^self topFillValue].! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:27'!topFillDepth ^self stackFillDepth: self stackFillSize - self stackFillEntryLength! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:27'!topFillDepthPut: value ^self stackFillDepth: self stackFillSize - self stackFillEntryLength put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/25/1998 14:36'!topFillRightX ^self stackFillRightX: self stackFillSize - self stackFillEntryLength! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/25/1998 14:36'!topFillRightXPut: value ^self stackFillRightX: self stackFillSize - self stackFillEntryLength put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:27'!topFillValue ^self stackFillValue: self stackFillSize - self stackFillEntryLength! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 10/30/1998 19:27'!topFillValuePut: value ^self stackFillValue: self stackFillSize - self stackFillEntryLength put: value! !!BalloonEngineBase methodsFor: 'accessing fills' stamp: 'ar 11/25/1998 15:19'!topRightX self stackFillSize = 0 ifTrue:[^999999999] ifFalse:[^self topFillRightX].! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/24/1998 20:05'!loadArrayTransformFrom: transformOop into: destPtr length: n "Load a transformation from the given array." | value | self inline: false. self var: #destPtr declareC:'float *destPtr'. 0 to: n-1 do:[:i| value _ interpreterProxy fetchPointer: i ofObject: transformOop. ((interpreterProxy isIntegerObject: value) or:[interpreterProxy isFloatObject: value]) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isIntegerObject: value) ifTrue:[destPtr at: i put: (self cCoerce: (interpreterProxy integerValueOf: value) asFloat to:'float')] ifFalse:[destPtr at: i put: (self cCoerce: (interpreterProxy floatValueOf: value) to: 'float')]. ].! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/25/1998 21:04'!loadColorTransformFrom: transformOop "Load a 2x3 transformation matrix from the given oop. Return true if the matrix is not nil, false otherwise" | okay transform | self var: #transform declareC:'float *transform'. transform _ self colorTransform. self hasColorTransformPut: 0. okay _ self loadTransformFrom: transformOop into: transform length: 8. okay ifFalse:[^false]. self hasColorTransformPut: 1. "Scale transform to be in 0-256 range" transform at: 1 put: (transform at: 1) * (self cCoerce: 256.0 to:'float'). transform at: 3 put: (transform at: 3) * (self cCoerce: 256.0 to:'float'). transform at: 5 put: (transform at: 5) * (self cCoerce: 256.0 to:'float'). transform at: 7 put: (transform at: 7) * (self cCoerce: 256.0 to:'float'). ^okay! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/11/1998 22:21'!loadEdgeStateFrom: edgeOop | edge | self inline: false. edge _ self lastExportedEdgeGet. (interpreterProxy slotSizeOf: edgeOop) < ETBalloonEdgeDataSize ifTrue:[^interpreterProxy primitiveFail]. self edgeXValueOf: edge put: (interpreterProxy fetchInteger: ETXValueIndex ofObject: edgeOop). self edgeYValueOf: edge put: (interpreterProxy fetchInteger: ETYValueIndex ofObject: edgeOop). self edgeZValueOf: edge put: (interpreterProxy fetchInteger: ETZValueIndex ofObject: edgeOop). self edgeNumLinesOf: edge put: (interpreterProxy fetchInteger: ETLinesIndex ofObject: edgeOop). ^edge! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/24/1998 21:33'!loadEdgeTransformFrom: transformOop "Load a 2x3 transformation matrix from the given oop. Return true if the matrix is not nil, false otherwise" | transform okay | self inline: false. self var: #transform declareC:'float *transform'. self hasEdgeTransformPut: 0. transform _ self edgeTransform. okay _ self loadTransformFrom: transformOop into: transform length: 6. interpreterProxy failed ifTrue:[^nil]. okay ifFalse:[^false]. self hasEdgeTransformPut: 1. "Add the fill offset to the matrix" transform at: 2 put: (self cCoerce: (transform at: 2) + self destOffsetXGet asFloat to:'float'). transform at: 5 put: (self cCoerce: (transform at: 5) + self destOffsetYGet asFloat to:'float'). ^true! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/25/1998 17:26'!loadFormsFrom: arrayOop "Check all the forms from arrayOop." | formOop bmBits bmBitsSize bmWidth bmHeight bmDepth ppw bmRaster | (interpreterProxy fetchClassOf: arrayOop) == interpreterProxy classArray ifFalse:[^false]. formArray _ arrayOop. 0 to: (interpreterProxy slotSizeOf: formArray) - 1 do:[:i| formOop _ interpreterProxy fetchPointer: i ofObject: formArray. (interpreterProxy isIntegerObject: formOop) ifTrue:[^false]. (interpreterProxy isPointers: formOop) ifFalse:[^false]. (interpreterProxy slotSizeOf: formOop) < 5 ifTrue:[^false]. bmBits _ interpreterProxy fetchPointer: 0 ofObject: formOop. (interpreterProxy fetchClassOf: bmBits) == interpreterProxy classBitmap ifFalse:[^false]. bmBitsSize _ interpreterProxy slotSizeOf: bmBits. bmWidth _ interpreterProxy fetchInteger: 1 ofObject: formOop. bmHeight _ interpreterProxy fetchInteger: 2 ofObject: formOop. bmDepth _ interpreterProxy fetchInteger: 3 ofObject: formOop. interpreterProxy failed ifTrue:[^false]. (bmWidth >= 0 and:[bmHeight >= 0]) ifFalse:[^false]. ppw _ 32 // bmDepth. bmRaster _ bmWidth + (ppw-1) // ppw. bmBitsSize = (bmRaster * bmHeight) ifFalse:[^false]. ]. ^true! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 10/27/1998 21:24'!loadPoint: pointArray from: pointOop "Load the contents of pointOop into pointArray" | value | self inline: false. self var: #pointArray declareC:'int *pointArray'. (interpreterProxy fetchClassOf: pointOop) = interpreterProxy classPoint ifFalse:[^interpreterProxy primitiveFail]. value _ interpreterProxy fetchPointer: 0 ofObject: pointOop. ((interpreterProxy isIntegerObject: value) or:[interpreterProxy isFloatObject: value]) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isIntegerObject: value) ifTrue:[pointArray at: 0 put: (interpreterProxy integerValueOf: value)] ifFalse:[pointArray at: 0 put: (interpreterProxy floatValueOf: value) asInteger]. value _ interpreterProxy fetchPointer: 1 ofObject: pointOop. ((interpreterProxy isIntegerObject: value) or:[interpreterProxy isFloatObject: value]) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isIntegerObject: value) ifTrue:[pointArray at: 1 put: (interpreterProxy integerValueOf: value)] ifFalse:[pointArray at: 1 put: (interpreterProxy floatValueOf: value) asInteger].! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 10/28/1998 00:46'!loadSpanBufferFrom: spanOop "Load the span buffer from the given oop." self inline: false. (interpreterProxy fetchClassOf: spanOop) = (interpreterProxy classBitmap) ifFalse:[^false]. spanBuffer _ interpreterProxy firstIndexableField: spanOop. "Leave last entry unused to avoid complications" self spanSizePut: (interpreterProxy slotSizeOf: spanOop) - 1. ^true! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/25/1998 23:22'!loadTransformFrom: transformOop into: destPtr length: n "Load a transformation from transformOop into the float array defined by destPtr. The transformation is assumed to be either an array or a FloatArray of length n." self inline: false. self var: #destPtr declareC:'float *destPtr'. transformOop = interpreterProxy nilObject ifTrue:[^false]. (interpreterProxy isIntegerObject: transformOop) ifTrue:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: transformOop) = n ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isWords: transformOop) ifTrue:[self loadWordTransformFrom: transformOop into: destPtr length: n] ifFalse:[self loadArrayTransformFrom: transformOop into: destPtr length: n]. ^true! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/24/1998 20:03'!loadWordTransformFrom: transformOop into: destPtr length: n "Load a float array transformation from the given oop" | srcPtr | self inline: false. self var: #srcPtr declareC:'float *srcPtr'. self var: #destPtr declareC:'float *destPtr'. srcPtr _ self cCoerce: (interpreterProxy firstIndexableField: transformOop) to: 'float *'. 0 to: n-1 do:[:i| destPtr at: i put: (srcPtr at: i)].! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 10/28/1998 19:37'!loadWorkBufferFrom: wbOop "Load the working buffer from the given oop" self inline: false. (interpreterProxy isIntegerObject: wbOop) ifTrue:[^false]. (interpreterProxy isWords: wbOop) ifFalse:[^false]. (interpreterProxy slotSizeOf: wbOop) < GWMinimalSize ifTrue:[^false]. workBuffer _ interpreterProxy firstIndexableField: wbOop. self magicNumberGet = GWMagicNumber ifFalse:[^false]. "Sanity checks" (self wbSizeGet = (interpreterProxy slotSizeOf: wbOop)) ifFalse:[^false]. self objStartGet = GWHeaderSize ifFalse:[^false]. "Load buffers" objBuffer _ workBuffer + self objStartGet. getBuffer _ objBuffer + self objUsedGet. aetBuffer _ getBuffer + self getUsedGet. "Make sure we don't exceed the work buffer" GWHeaderSize + self objUsedGet + self getUsedGet + self aetUsedGet > self wbSizeGet ifTrue:[^false]. ^true! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 11/25/1998 00:36'!quickLoadEngineFrom: engineOop "Load the minimal required state from the engineOop, e.g., just the work buffer." self inline: false. interpreterProxy failed ifTrue:[^false]. (interpreterProxy isIntegerObject: engineOop) ifTrue:[^false]. (interpreterProxy isPointers: engineOop) ifFalse:[^false]. (interpreterProxy slotSizeOf: engineOop) < BEBalloonEngineSize ifTrue:[^false]. engine _ engineOop. (self loadWorkBufferFrom: (interpreterProxy fetchPointer: BEWorkBufferIndex ofObject: engineOop)) ifFalse:[^false]. self stopReasonPut: 0. objUsed _ self objUsedGet. engineStopped _ false. ^true! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 10/28/1998 21:06'!quickLoadEngineFrom: oop requiredState: requiredState self inline: false. (self quickLoadEngineFrom: oop) ifFalse:[^false]. self stateGet = requiredState ifTrue:[^true]. self stopReasonPut: GErrorBadState. ^false! !!BalloonEngineBase methodsFor: 'loading state' stamp: 'ar 10/31/1998 17:23'!quickLoadEngineFrom: oop requiredState: requiredState or: alternativeState self inline: false. (self quickLoadEngineFrom: oop) ifFalse:[^false]. self stateGet = requiredState ifTrue:[^true]. self stateGet = alternativeState ifTrue:[^true]. self stopReasonPut: GErrorBadState. ^false! !!BalloonEngineBase methodsFor: 'storing state' stamp: 'ar 11/11/1998 22:21'!storeEdgeStateFrom: edge into: edgeOop self inline: false. (interpreterProxy slotSizeOf: edgeOop) < ETBalloonEdgeDataSize ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy storeInteger: ETIndexIndex ofObject: edgeOop withValue: (self objectIndexOf: edge). interpreterProxy storeInteger: ETXValueIndex ofObject: edgeOop withValue: (self edgeXValueOf: edge). interpreterProxy storeInteger: ETYValueIndex ofObject: edgeOop withValue: (self currentYGet). interpreterProxy storeInteger: ETZValueIndex ofObject: edgeOop withValue: (self edgeZValueOf: edge). interpreterProxy storeInteger: ETLinesIndex ofObject: edgeOop withValue: (self edgeNumLinesOf: edge). self lastExportedEdgePut: edge.! !!BalloonEngineBase methodsFor: 'storing state' stamp: 'ar 11/25/1998 00:36'!storeEngineStateInto: oop self objUsedPut: objUsed.! !!BalloonEngineBase methodsFor: 'storing state' stamp: 'ar 11/11/1998 22:24'!storeFillStateInto: fillOop | fillIndex leftX rightX | self inline: false. fillIndex _ self lastExportedFillGet. leftX _ self lastExportedLeftXGet. rightX _ self lastExportedRightXGet. (interpreterProxy slotSizeOf: fillOop) < FTBalloonFillDataSize ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy storeInteger: FTIndexIndex ofObject: fillOop withValue: (self objectIndexOf: fillIndex). interpreterProxy storeInteger: FTMinXIndex ofObject: fillOop withValue: leftX. interpreterProxy storeInteger: FTMaxXIndex ofObject: fillOop withValue: rightX. interpreterProxy storeInteger: FTYValueIndex ofObject: fillOop withValue: self currentYGet.! !!BalloonEngineBase methodsFor: 'storing state' stamp: 'ar 11/9/1998 15:34'!storeStopStateIntoEdge: edgeOop fill: fillOop | reason edge | reason _ self stopReasonGet. reason = GErrorGETEntry ifTrue:[ edge _ getBuffer at: self getStartGet. self storeEdgeStateFrom: edge into: edgeOop. self getStartPut: self getStartGet + 1. ]. reason = GErrorFillEntry ifTrue:[ self storeFillStateInto: fillOop. ]. reason = GErrorAETEntry ifTrue:[ edge _ aetBuffer at: self aetStartGet. self storeEdgeStateFrom: edge into: edgeOop. "Do not advance to the next aet entry yet" "self aetStartPut: self aetStartGet + 1." ].! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/9/1998 15:34'!areEdgeFillsValid: edge ^((self objectHeaderOf: edge) bitAnd: GEEdgeFillsInvalid) = 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 10/31/1998 17:06'!finishedProcessing "Return true if processing is finished" ^self stateGet = GEStateCompleted! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/24/1998 19:39'!hasColorTransform ^self hasColorTransformGet ~= 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/24/1998 19:38'!hasEdgeTransform ^self hasEdgeTransformGet ~= 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 10/29/1998 19:36'!isEdge: edge | type | type _ self objectTypeOf: edge. type > GEPrimitiveEdgeMask ifTrue:[^false]. ^((self objectTypeOf: edge) bitAnd: GEPrimitiveEdgeMask) ~= 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/7/1998 21:28'!isFill: fill ^(self isFillColor: fill) or:[self isRealFill: fill]! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 10/29/1998 19:31'!isFillColor: fill ^((self makeUnsignedFrom: fill) bitAnd: 16rFF000000) ~= 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/25/1998 00:43'!isObject: obj ^obj >= 0 and:[obj < objUsed]! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/7/1998 21:28'!isRealFill: fill ^((self objectTypeOf: fill) bitAnd: GEPrimitiveFillMask) ~= 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 10/31/1998 23:12'!isStackEntry: entry ^entry >= self wbTopGet and:[entry < self wbSizeGet]! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 10/30/1998 17:38'!isStackIndex: index ^index >= 0 and:[index < self wbStackSize]! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/9/1998 15:36'!isWide: object ^((self objectTypeOf: object) bitAnd: GEPrimitiveWide) ~= 0! !!BalloonEngineBase methodsFor: 'testing' stamp: 'ar 11/25/1998 00:21'!needsFlush ^self needsFlushGet ~= 0! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:08'!primitiveGetAALevel self export: true. self inline: false. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. interpreterProxy pushInteger: self aaLevelGet.! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:10'!primitiveGetClipRect | rectOop pointOop | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. rectOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isPointers: rectOop) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: rectOop) < 2 ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy pushRemappableOop: rectOop. pointOop _ interpreterProxy makePointwithxValue: self clipMinXGet yValue: self clipMinYGet. rectOop _ interpreterProxy popRemappableOop. interpreterProxy storePointer: 0 ofObject: rectOop withValue: pointOop. interpreterProxy pushRemappableOop: rectOop. pointOop _ interpreterProxy makePointwithxValue: self clipMaxXGet yValue: self clipMaxYGet. rectOop _ interpreterProxy popRemappableOop. interpreterProxy storePointer: 1 ofObject: rectOop withValue: pointOop. interpreterProxy pop: 2. interpreterProxy push: rectOop.! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:13'!primitiveGetCounts | statOop stats | self export: true. self inline: false. self var: #stats declareC:'int *stats'. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. statOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isWords: statOop) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: statOop) < 9 ifTrue:[^interpreterProxy primitiveFail]. stats _ interpreterProxy firstIndexableField: statOop. stats at: 0 put: (stats at: 0) + (workBuffer at: GWCountInitializing). stats at: 1 put: (stats at: 1) + (workBuffer at: GWCountFinishTest). stats at: 2 put: (stats at: 2) + (workBuffer at: GWCountNextGETEntry). stats at: 3 put: (stats at: 3) + (workBuffer at: GWCountAddAETEntry). stats at: 4 put: (stats at: 4) + (workBuffer at: GWCountNextFillEntry). stats at: 5 put: (stats at: 5) + (workBuffer at: GWCountMergeFill). stats at: 6 put: (stats at: 6) + (workBuffer at: GWCountDisplaySpan). stats at: 7 put: (stats at: 7) + (workBuffer at: GWCountNextAETEntry). stats at: 8 put: (stats at: 8) + (workBuffer at: GWCountChangeAETEntry). interpreterProxy pop: 1. "Leave rcvr on stack"! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:14'!primitiveGetDepth self export: true. self inline: false. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. interpreterProxy pushInteger: self currentZGet.! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:10'!primitiveGetFailureReason "Return the reason why the last operation failed." self export: true. self inline: false. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. "Note -- don't call loadEngineFrom here because this will override the stopReason with Zero" (interpreterProxy isIntegerObject: engine) ifTrue:[^false]. (interpreterProxy isPointers: engine) ifFalse:[^false]. (interpreterProxy slotSizeOf: engine) < BEBalloonEngineSize ifTrue:[^false]. (self loadWorkBufferFrom: (interpreterProxy fetchPointer: BEWorkBufferIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 1. interpreterProxy pushInteger: self stopReasonGet.! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:11'!primitiveGetOffset | pointOop | self export: true. self inline: false. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. pointOop _ interpreterProxy makePointwithxValue: self destOffsetXGet yValue: self destOffsetYGet. interpreterProxy pop: 1. interpreterProxy push: pointOop.! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:07'!primitiveGetTimes | statOop stats | self export: true. self inline: false. self var: #stats declareC:'int *stats'. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. statOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isWords: statOop) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: statOop) < 9 ifTrue:[^interpreterProxy primitiveFail]. stats _ interpreterProxy firstIndexableField: statOop. stats at: 0 put: (stats at: 0) + (workBuffer at: GWTimeInitializing). stats at: 1 put: (stats at: 1) + (workBuffer at: GWTimeFinishTest). stats at: 2 put: (stats at: 2) + (workBuffer at: GWTimeNextGETEntry). stats at: 3 put: (stats at: 3) + (workBuffer at: GWTimeAddAETEntry). stats at: 4 put: (stats at: 4) + (workBuffer at: GWTimeNextFillEntry). stats at: 5 put: (stats at: 5) + (workBuffer at: GWTimeMergeFill). stats at: 6 put: (stats at: 6) + (workBuffer at: GWTimeDisplaySpan). stats at: 7 put: (stats at: 7) + (workBuffer at: GWTimeNextAETEntry). stats at: 8 put: (stats at: 8) + (workBuffer at: GWTimeChangeAETEntry). interpreterProxy pop: 1. "Leave rcvr on stack"! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:12'!primitiveNeedsFlush | needFlush | self export: true. self inline: false. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. needFlush _ self needsFlush. self storeEngineStateInto: engine. interpreterProxy pop: 1. interpreterProxy pushBool: needFlush.! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:14'!primitiveNeedsFlushPut | needFlush | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. needFlush _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. needFlush _ interpreterProxy booleanValueOf: needFlush. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. needFlush == true ifTrue:[self needsFlushPut: 1] ifFalse:[self needsFlushPut: 0]. self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack"! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:12'!primitiveSetAALevel | level | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. level _ interpreterProxy stackIntegerValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. self setAALevel: level. self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leace rcvr on stack"! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/16/2000 20:03'!primitiveSetBitBltPlugin "Primitive. Set the BitBlt plugin to use." | pluginName length ptr needReload | self export: true. self var: #ptr declareC:'char *ptr'. pluginName _ interpreterProxy stackValue: 0. "Must be string to work" (interpreterProxy isBytes: pluginName) ifFalse:[^interpreterProxy primitiveFail]. length _ interpreterProxy byteSizeOf: pluginName. length >= 256 ifTrue:[^interpreterProxy primitiveFail]. ptr _ interpreterProxy firstIndexableField: pluginName. needReload _ false. 0 to: length-1 do:[:i| "Compare and store the plugin to be used" (bbPluginName at: i) = (ptr at: i) ifFalse:[ bbPluginName at: i put: (ptr at: i). needReload _ true]]. (bbPluginName at: length) = 0 ifFalse:[ bbPluginName at: length put: 0. needReload _ true]. needReload ifTrue:[ self initialiseModule ifFalse:[^interpreterProxy primitiveFail]]. interpreterProxy pop: 1. "Return receiver"! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:05'!primitiveSetClipRect | rectOop | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. rectOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy isPointers: rectOop) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: rectOop) < 2 ifTrue:[^interpreterProxy primitiveFail]. self loadPoint: self point1Get from: (interpreterProxy fetchPointer: 0 ofObject: rectOop). self loadPoint: self point2Get from: (interpreterProxy fetchPointer: 1 ofObject: rectOop). interpreterProxy failed ifFalse:[ self clipMinXPut: (self point1Get at: 0). self clipMinYPut: (self point1Get at: 1). self clipMaxXPut: (self point2Get at: 0). self clipMaxYPut: (self point2Get at: 1). self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" ].! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:11'!primitiveSetColorTransform | transformOop | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. transformOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. self loadColorTransformFrom: transformOop. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" ].! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:06'!primitiveSetDepth | depth | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. depth _ interpreterProxy stackIntegerValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. self currentZPut: depth. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" ].! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:14'!primitiveSetEdgeTransform | transformOop | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. transformOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. self loadEdgeTransformFrom: transformOop. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" ].! !!BalloonEngineBase methodsFor: 'primitives-access' stamp: 'ar 5/11/2000 23:13'!primitiveSetOffset | pointOop | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. pointOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy fetchClassOf: pointOop) = interpreterProxy classPoint ifFalse:[^interpreterProxy primitiveFail]. self loadPoint: self point1Get from: pointOop. interpreterProxy failed ifFalse:[ self destOffsetXPut: (self point1Get at: 0). self destOffsetYPut: (self point1Get at: 1). self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" ].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:58'!primitiveAddActiveEdgeEntry "Note: No need to load either bitBlt or spanBuffer" | edgeOop edge | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. edgeOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateWaitingForEdge) ifFalse:[^interpreterProxy primitiveFail]. edge _ self loadEdgeStateFrom: edgeOop. interpreterProxy failed ifTrue:[^nil]. (self needAvailableSpace: 1) ifFalse:[^interpreterProxy primitiveFail]. (self edgeNumLinesOf: edge) > 0 ifTrue:[ self insertEdgeIntoAET: edge. ]. engineStopped ifTrue:[^interpreterProxy primitiveFail]. self statePut: GEStateAddingFromGET. "Back to adding edges from GET" self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" doProfileStats ifTrue:[ self incrementStat: GWCountAddAETEntry by: 1. self incrementStat: GWTimeAddAETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:59'!primitiveChangedActiveEdgeEntry "Note: No need to load either bitBlt or spanBuffer" | edgeOop edge | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. edgeOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateWaitingChange) ifFalse:[^interpreterProxy primitiveFail]. edge _ self loadEdgeStateFrom: edgeOop. interpreterProxy failed ifTrue:[^nil]. (self edgeNumLinesOf: edge) = 0 ifTrue:[ self removeFirstAETEntry] ifFalse:[ self resortFirstAETEntry. self aetStartPut: self aetStartGet + 1]. self statePut: GEStateUpdateEdges. "Back to updating edges" self storeEngineStateInto: engine. interpreterProxy pop: 1. "Leave rcvr on stack" doProfileStats ifTrue:[ self incrementStat: GWCountChangeAETEntry by: 1. self incrementStat: GWTimeChangeAETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:59'!primitiveDisplaySpanBuffer "Note: Must load bitBlt and spanBuffer" self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateBlitBuffer) ifFalse:[^interpreterProxy primitiveFail]. "Load span buffer and bitBlt" (self loadSpanBufferFrom: (interpreterProxy fetchPointer: BESpanIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. (self loadBitBltFrom: (interpreterProxy fetchPointer: BEBitBltIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. (self currentYGet bitAnd: self aaScanMaskGet) = self aaScanMaskGet ifTrue:[ self displaySpanBufferAt: self currentYGet. self postDisplayAction. ]. self finishedProcessing ifFalse:[ self aetStartPut: 0. self currentYPut: self currentYGet + 1. self statePut: GEStateUpdateEdges]. self storeEngineStateInto: engine. doProfileStats ifTrue:[ self incrementStat: GWCountDisplaySpan by: 1. self incrementStat: GWTimeDisplaySpan by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:59'!primitiveInitializeProcessing "Note: No need to load bitBlt but must load spanBuffer" self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. "Load span buffer for clear operation" (self loadSpanBufferFrom: (interpreterProxy fetchPointer: BESpanIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. self initializeGETProcessing. engineStopped ifTrue:[^interpreterProxy primitiveFail]. self statePut: GEStateAddingFromGET. "Initialized" interpreterProxy failed ifFalse:[self storeEngineStateInto: engine]. doProfileStats ifTrue:[ self incrementStat: GWCountInitializing by: 1. self incrementStat: GWTimeInitializing by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:59'!primitiveMergeFillFrom "Note: No need to load bitBlt but must load spanBuffer" | fillOop bitsOop value | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. fillOop _ interpreterProxy stackObjectValue: 0. bitsOop _ interpreterProxy stackObjectValue: 1. engine _ interpreterProxy stackObjectValue: 2. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateWaitingForFill) ifFalse:[^interpreterProxy primitiveFail]. "Load span buffer for merging the fill" (self loadSpanBufferFrom: (interpreterProxy fetchPointer: BESpanIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. "Check bitmap" (interpreterProxy fetchClassOf: bitsOop) = interpreterProxy classBitmap ifFalse:[^interpreterProxy primitiveFail]. "Check fillOop" (interpreterProxy slotSizeOf: fillOop) < FTBalloonFillDataSize ifTrue:[^interpreterProxy primitiveFail]. "Check if this was the fill we have exported" value _ interpreterProxy fetchInteger: FTIndexIndex ofObject: fillOop. (self objectIndexOf: self lastExportedFillGet) = value ifFalse:[^interpreterProxy primitiveFail]. value _ interpreterProxy fetchInteger: FTMinXIndex ofObject: fillOop. self lastExportedLeftXGet = value ifFalse:[^interpreterProxy primitiveFail]. value _ interpreterProxy fetchInteger: FTMaxXIndex ofObject: fillOop. self lastExportedRightXGet = value ifFalse:[^interpreterProxy primitiveFail]. (interpreterProxy slotSizeOf: bitsOop) < (self lastExportedRightXGet - self lastExportedLeftXGet) ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy failed ifTrue:[^nil]. self fillBitmapSpan: (interpreterProxy firstIndexableField: bitsOop) from: self lastExportedLeftXGet to: self lastExportedRightXGet. self statePut: GEStateScanningAET. "Back to scanning AET" self storeEngineStateInto: engine. interpreterProxy pop: 2. "Leave rcvr on stack" doProfileStats ifTrue:[ self incrementStat: GWCountMergeFill by: 1. self incrementStat: GWTimeMergeFill by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:59'!primitiveNextActiveEdgeEntry "Note: No need to load either bitBlt or spanBuffer" | edgeOop hasEdge edge | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. edgeOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUpdateEdges or: GEStateCompleted) ifFalse:[^interpreterProxy primitiveFail]. hasEdge _ false. self stateGet = GEStateCompleted ifFalse:[ hasEdge _ self findNextExternalUpdateFromAET. hasEdge ifTrue:[ edge _ aetBuffer at: self aetStartGet. self storeEdgeStateFrom: edge into: edgeOop. "Do not advance to the next aet entry yet" "self aetStartPut: self aetStartGet + 1." self statePut: GEStateWaitingChange. "Wait for changed edge" ] ifFalse:[self statePut: GEStateAddingFromGET]. "Start over" ]. interpreterProxy failed ifTrue:[^nil]. self storeEngineStateInto: engine. interpreterProxy pop: 2. interpreterProxy pushBool: hasEdge not. doProfileStats ifTrue:[ self incrementStat: GWCountNextAETEntry by: 1. self incrementStat: GWTimeNextAETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 14:59'!primitiveNextFillEntry "Note: No need to load bitBlt but must load spanBuffer" | fillOop hasFill | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. fillOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateScanningAET) ifFalse:[^interpreterProxy primitiveFail]. "Load span buffer for internal handling of fills" (self loadSpanBufferFrom: (interpreterProxy fetchPointer: BESpanIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. (self loadFormsFrom: (interpreterProxy fetchPointer: BEFormsIndex ofObject: engine)) ifFalse:[^interpreterProxy primitiveFail]. "Check if we have to clear the span buffer before proceeding" (self clearSpanBufferGet = 0) ifFalse:[ (self currentYGet bitAnd: self aaScanMaskGet) = 0 ifTrue:[self clearSpanBuffer]. self clearSpanBufferPut: 0]. hasFill _ self findNextExternalFillFromAET. engineStopped ifTrue:[^interpreterProxy primitiveFail]. hasFill ifTrue:[self storeFillStateInto: fillOop]. interpreterProxy failed ifFalse:[ hasFill ifTrue:[ self statePut: GEStateWaitingForFill] ifFalse:[ self wbStackClear. self spanEndAAPut: 0. self statePut: GEStateBlitBuffer]. self storeEngineStateInto: engine. interpreterProxy pop: 2. interpreterProxy pushBool: hasFill not. doProfileStats ifTrue:[ self incrementStat: GWCountNextFillEntry by: 1. self incrementStat: GWTimeNextFillEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. ].! !!BalloonEngineBase methodsFor: 'primitives-incremental' stamp: 'ar 5/13/2000 15:00'!primitiveNextGlobalEdgeEntry "Note: No need to load either bitBlt or spanBuffer" | edgeOop hasEdge edge | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. edgeOop _ interpreterProxy stackObjectValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateAddingFromGET) ifFalse:[^interpreterProxy primitiveFail]. hasEdge _ self findNextExternalEntryFromGET. hasEdge ifTrue:[ edge _ getBuffer at: self getStartGet. self storeEdgeStateFrom: edge into: edgeOop. self getStartPut: self getStartGet + 1]. interpreterProxy failed ifTrue:[^nil]. hasEdge ifTrue:[ self statePut: GEStateWaitingForEdge] "Wait for adding edges" ifFalse:[ "Start scanning the AET" self statePut: GEStateScanningAET. self clearSpanBufferPut: 1. "Clear span buffer at next entry" self aetStartPut: 0. self wbStackClear]. self storeEngineStateInto: engine. interpreterProxy pop: 2. interpreterProxy pushBool: hasEdge not. doProfileStats ifTrue:[ self incrementStat: GWCountNextGETEntry by: 1. self incrementStat: GWTimeNextGETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-rendering' stamp: 'ar 5/12/2000 16:40'!loadRenderingState "Load the entire state from the interpreter for the rendering primitives" | edgeOop fillOop state | self inline: false. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. fillOop _ interpreterProxy stackObjectValue: 0. edgeOop _ interpreterProxy stackObjectValue: 1. engine _ interpreterProxy stackObjectValue: 2. interpreterProxy failed ifTrue:[^false]. (self quickLoadEngineFrom: engine) ifFalse:[^false]. "Load span buffer and bitBlt" (self loadSpanBufferFrom: (interpreterProxy fetchPointer: BESpanIndex ofObject: engine)) ifFalse:[^false]. (self loadBitBltFrom: (interpreterProxy fetchPointer: BEBitBltIndex ofObject: engine)) ifFalse:[^false]. (self loadFormsFrom: (interpreterProxy fetchPointer: BEFormsIndex ofObject: engine)) ifFalse:[^false]. "Check edgeOop and fillOop" (interpreterProxy slotSizeOf: edgeOop) < ETBalloonEdgeDataSize ifTrue:[^false]. (interpreterProxy slotSizeOf: fillOop) < FTBalloonFillDataSize ifTrue:[^false]. "Note: Rendering can only take place if we're not in one of the intermediate (e.g., external) states." state _ self stateGet. (state = GEStateWaitingForEdge or:[ state = GEStateWaitingForFill or:[ state = GEStateWaitingChange]]) ifTrue:[^false]. ^true! !!BalloonEngineBase methodsFor: 'primitives-rendering' stamp: 'ar 5/11/2000 23:08'!primitiveRenderImage "Start/Proceed rendering the entire image" self export: true. self inline: false. self loadRenderingState ifFalse:[^interpreterProxy primitiveFail]. self proceedRenderingScanline. "Finish this scan line" engineStopped ifTrue:[^self storeRenderingState]. self proceedRenderingImage. "And go on as usual" self storeRenderingState.! !!BalloonEngineBase methodsFor: 'primitives-rendering' stamp: 'ar 5/11/2000 23:07'!primitiveRenderScanline "Start rendering the entire image" self export: true. self inline: false. self loadRenderingState ifFalse:[^interpreterProxy primitiveFail]. self proceedRenderingScanline. "Finish the current scan line" self storeRenderingState.! !!BalloonEngineBase methodsFor: 'primitives-rendering' stamp: 'ar 5/13/2000 15:00'!proceedRenderingImage "This is the main rendering entry" | external | self inline: false. [self finishedProcessing] whileFalse:[ doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. external _ self findNextExternalEntryFromGET. doProfileStats ifTrue:[ self incrementStat: GWCountNextGETEntry by: 1. self incrementStat: GWTimeNextGETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateAddingFromGET]. external ifTrue:[ self statePut: GEStateWaitingForEdge. ^self stopBecauseOf: GErrorGETEntry. ]. self aetStartPut: 0. self wbStackClear. self clearSpanBufferPut: 1. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. (self clearSpanBufferGet ~= 0 and:[(self currentYGet bitAnd: self aaScanMaskGet) = 0]) ifTrue:[self clearSpanBuffer]. self clearSpanBufferPut: 0. external _ self findNextExternalFillFromAET. doProfileStats ifTrue:[ self incrementStat: GWCountNextFillEntry by: 1. self incrementStat: GWTimeNextFillEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateScanningAET]. external ifTrue:[ self statePut: GEStateWaitingForFill. ^self stopBecauseOf: GErrorFillEntry. ]. self wbStackClear. self spanEndAAPut: 0. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. (self currentYGet bitAnd: self aaScanMaskGet) = self aaScanMaskGet ifTrue:[ self displaySpanBufferAt: self currentYGet. self postDisplayAction. ]. doProfileStats ifTrue:[ self incrementStat: GWCountDisplaySpan by: 1. self incrementStat: GWTimeDisplaySpan by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateBlitBuffer]. self finishedProcessing ifTrue:[^0]. self aetStartPut: 0. self currentYPut: self currentYGet + 1. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. external _ self findNextExternalUpdateFromAET. doProfileStats ifTrue:[ self incrementStat: GWCountNextAETEntry by: 1. self incrementStat: GWTimeNextAETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateUpdateEdges]. external ifTrue:[ self statePut: GEStateWaitingChange. ^self stopBecauseOf: GErrorAETEntry. ]. ].! !!BalloonEngineBase methodsFor: 'primitives-rendering' stamp: 'ar 5/13/2000 15:00'!proceedRenderingScanline "Proceed rendering the current scan line. This method may be called after some Smalltalk code has been executed inbetween." "This is the main rendering entry" | external state | self inline: false. state _ self stateGet. state = GEStateUnlocked ifTrue:[ self initializeGETProcessing. engineStopped ifTrue:[^0]. state _ GEStateAddingFromGET. ]. state = GEStateAddingFromGET ifTrue:[ doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. external _ self findNextExternalEntryFromGET. doProfileStats ifTrue:[ self incrementStat: GWCountNextGETEntry by: 1. self incrementStat: GWTimeNextGETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateAddingFromGET]. external ifTrue:[ self statePut: GEStateWaitingForEdge. ^self stopBecauseOf: GErrorGETEntry. ]. self aetStartPut: 0. self wbStackClear. self clearSpanBufferPut: 1. state _ GEStateScanningAET. ]. state = GEStateScanningAET ifTrue:[ doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. (self clearSpanBufferGet ~= 0 and:[(self currentYGet bitAnd: self aaScanMaskGet) = 0]) ifTrue:[self clearSpanBuffer]. self clearSpanBufferPut: 0. external _ self findNextExternalFillFromAET. doProfileStats ifTrue:[ self incrementStat: GWCountNextFillEntry by: 1. self incrementStat: GWTimeNextFillEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateScanningAET]. external ifTrue:[ self statePut: GEStateWaitingForFill. ^self stopBecauseOf: GErrorFillEntry. ]. state _ GEStateBlitBuffer. self wbStackClear. self spanEndAAPut: 0. ]. state = GEStateBlitBuffer ifTrue:[ doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. (self currentYGet bitAnd: self aaScanMaskGet) = self aaScanMaskGet ifTrue:[ self displaySpanBufferAt: self currentYGet. self postDisplayAction. ]. doProfileStats ifTrue:[ self incrementStat: GWCountDisplaySpan by: 1. self incrementStat: GWTimeDisplaySpan by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateBlitBuffer]. self finishedProcessing ifTrue:[^0]. state _ GEStateUpdateEdges. self aetStartPut: 0. self currentYPut: self currentYGet + 1. ]. state = GEStateUpdateEdges ifTrue:[ doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. external _ self findNextExternalUpdateFromAET. doProfileStats ifTrue:[ self incrementStat: GWCountNextAETEntry by: 1. self incrementStat: GWTimeNextAETEntry by: (interpreterProxy ioMicroMSecs - geProfileTime)]. engineStopped ifTrue:[^self statePut: GEStateUpdateEdges]. external ifTrue:[ self statePut: GEStateWaitingChange. ^self stopBecauseOf: GErrorAETEntry. ]. self statePut: GEStateAddingFromGET. ].! !!BalloonEngineBase methodsFor: 'primitives-rendering' stamp: 'ar 10/31/1998 23:54'!storeRenderingState self inline: false. interpreterProxy failed ifTrue:[^nil]. engineStopped ifTrue:[ "Check the stop reason and store the required information" self storeStopStateIntoEdge: (interpreterProxy stackObjectValue: 1) fill: (interpreterProxy stackObjectValue: 0). ]. self storeEngineStateInto: engine. interpreterProxy pop: 3. interpreterProxy pushInteger: self stopReasonGet.! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/11/2000 23:06'!primitiveAbortProcessing self export: true. self inline: false. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. self statePut: GEStateCompleted. self storeEngineStateInto: engine.! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/11/2000 23:12'!primitiveCopyBuffer | buf1 buf2 diff src dst | self export: true. self inline: false. self var: #src declareC:'int * src'. self var: #dst declareC:'int * dst'. interpreterProxy methodArgumentCount = 2 ifFalse:[^interpreterProxy primitiveFail]. buf2 _ interpreterProxy stackObjectValue: 0. buf1 _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. "Make sure the old buffer is properly initialized" (self loadWorkBufferFrom: buf1) ifFalse:[^interpreterProxy primitiveFail]. "Make sure the buffers are of the same type" (interpreterProxy fetchClassOf: buf1) = (interpreterProxy fetchClassOf: buf2) ifFalse:[^interpreterProxy primitiveFail]. "Make sure buf2 is at least of the size of buf1" diff _ (interpreterProxy slotSizeOf: buf2) - (interpreterProxy slotSizeOf: buf1). diff < 0 ifTrue:[^interpreterProxy primitiveFail]. "Okay - ready for copying. First of all just copy the contents up to wbTop" src _ workBuffer. dst _ interpreterProxy firstIndexableField: buf2. 0 to: self wbTopGet-1 do:[:i| dst at: i put: (src at: i). ]. "Adjust wbSize and wbTop in the new buffer" dst at: GWBufferTop put: self wbTopGet + diff. dst at: GWSize put: self wbSizeGet + diff. "Now copy the entries from wbTop to wbSize" src _ src + self wbTopGet. dst _ dst + self wbTopGet + diff. 0 to: (self wbSizeGet - self wbTopGet - 1) do:[:i| dst at: i put: (src at: i). ]. "Okay, done. Check the new buffer by loading the state from it" (self loadWorkBufferFrom: buf2) ifFalse:[^interpreterProxy primitiveFail]. interpreterProxy pop: 2. "Leave rcvr on stack"! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/11/2000 23:05'!primitiveDoProfileStats "Turn on/off profiling. Return the old value of the flag." | oldValue newValue | self inline: false. self export: true. oldValue _ doProfileStats. newValue _ interpreterProxy stackObjectValue: 0. newValue _ interpreterProxy booleanValueOf: newValue. interpreterProxy failed ifFalse:[ doProfileStats _ newValue. interpreterProxy pop: 2. "Pop rcvr, arg" interpreterProxy pushBool: oldValue. ].! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/13/2000 14:59'!primitiveFinishedProcessing | finished | self export: true. self inline: false. doProfileStats ifTrue:[geProfileTime _ interpreterProxy ioMicroMSecs]. interpreterProxy methodArgumentCount = 0 ifFalse:[^interpreterProxy primitiveFail]. engine _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine) ifFalse:[^interpreterProxy primitiveFail]. finished _ self finishedProcessing. self storeEngineStateInto: engine. interpreterProxy pop: 1. interpreterProxy pushBool: finished. doProfileStats ifTrue:[ self incrementStat: GWCountFinishTest by: 1. self incrementStat: GWTimeFinishTest by: (interpreterProxy ioMicroMSecs - geProfileTime)].! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/11/2000 23:09'!primitiveInitializeBuffer | wbOop size | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. wbOop _ interpreterProxy stackObjectValue: 0. interpreterProxy failed ifTrue:[^nil]. (interpreterProxy isWords: wbOop) ifFalse:[^interpreterProxy primitiveFail]. (size _ interpreterProxy slotSizeOf: wbOop) < GWMinimalSize ifTrue:[^interpreterProxy primitiveFail]. workBuffer _ interpreterProxy firstIndexableField: wbOop. objBuffer _ workBuffer + GWHeaderSize. self magicNumberPut: GWMagicNumber. self wbSizePut: size. self wbTopPut: size. self statePut: GEStateUnlocked. self objStartPut: GWHeaderSize. self objUsedPut: 4. "Dummy fill object" self objectTypeOf: 0 put: GEPrimitiveFill. self objectLengthOf: 0 put: 4. self objectIndexOf: 0 put: 0. self getStartPut: 0. self getUsedPut: 0. self aetStartPut: 0. self aetUsedPut: 0. self stopReasonPut: 0. self needsFlushPut: 0. self clipMinXPut: 0. self clipMaxXPut: 0. self clipMinYPut: 0. self clipMaxYPut: 0. self currentZPut: 0. self resetGraphicsEngineStats. self initEdgeTransform. self initColorTransform. interpreterProxy pop: 2. interpreterProxy push: wbOop.! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/11/2000 23:08'!primitiveRegisterExternalEdge | rightFillIndex leftFillIndex initialZ initialY initialX index edge | self export: true. self inline: false. interpreterProxy methodArgumentCount = 6 ifFalse:[^interpreterProxy primitiveFail]. rightFillIndex _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0). leftFillIndex _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 1). initialZ _ interpreterProxy stackIntegerValue: 2. initialY _ interpreterProxy stackIntegerValue: 3. initialX _ interpreterProxy stackIntegerValue: 4. index _ interpreterProxy stackIntegerValue: 5. engine _ interpreterProxy stackObjectValue: 6. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. (self allocateObjEntry: GEBaseEdgeSize) ifFalse:[^interpreterProxy primitiveFail]. "Make sure the fills are okay" (self isFillOkay: leftFillIndex) ifFalse:[^interpreterProxy primitiveFail]. (self isFillOkay: rightFillIndex) ifFalse:[^interpreterProxy primitiveFail]. edge _ objUsed. objUsed _ edge + GEBaseEdgeSize. "Install type and length" self objectTypeOf: edge put: GEPrimitiveEdge. self objectLengthOf: edge put: GEBaseEdgeSize. self objectIndexOf: edge put: index. "Install remaining stuff" self edgeXValueOf: edge put: initialX. self edgeYValueOf: edge put: initialY. self edgeZValueOf: edge put: initialZ. self edgeLeftFillOf: edge put: (self transformColor: leftFillIndex). self edgeRightFillOf: edge put: (self transformColor: rightFillIndex). engineStopped ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 6. "Leave rcvr on stack" ].! !!BalloonEngineBase methodsFor: 'primitives-other' stamp: 'ar 5/11/2000 23:14'!primitiveRegisterExternalFill | index fill | self export: true. self inline: false. interpreterProxy methodArgumentCount = 1 ifFalse:[^interpreterProxy primitiveFail]. index _ interpreterProxy stackIntegerValue: 0. engine _ interpreterProxy stackObjectValue: 1. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: engine requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. "Note: We *must* not allocate any fill with index 0" fill _ 0. [fill = 0] whileTrue:[ (self allocateObjEntry: GEBaseEdgeSize) ifFalse:[^interpreterProxy primitiveFail]. fill _ objUsed. objUsed _ fill + GEBaseFillSize. "Install type and length" self objectTypeOf: fill put: GEPrimitiveFill. self objectLengthOf: fill put: GEBaseFillSize. self objectIndexOf: fill put: index. ]. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 2. interpreterProxy pushInteger: fill. ].! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 10/29/1998 18:37'!allocateAETEntry: nSlots "Allocate n slots in the active edge table" ^self needAvailableSpace: nSlots! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 10/28/1998 21:06'!allocateGETEntry: nSlots "Allocate n slots in the global edge table" | srcIndex dstIndex | self inline: false. "First allocate nSlots in the AET" (self allocateAETEntry: nSlots) ifFalse:[^false]. self aetUsedGet = 0 ifFalse:["Then move the AET upwards" srcIndex _ self aetUsedGet. dstIndex _ self aetUsedGet + nSlots. 1 to: self aetUsedGet do:[:i| aetBuffer at: (dstIndex _ dstIndex - 1) put: (aetBuffer at: (srcIndex _ srcIndex - 1))]. ]. aetBuffer _ aetBuffer + nSlots. ^true! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 10/28/1998 21:16'!allocateObjEntry: nSlots "Allocate n slots in the object buffer" | srcIndex dstIndex | self inline: false. "First allocate nSlots in the GET" (self allocateGETEntry: nSlots) ifFalse:[^false]. self getUsedGet = 0 ifFalse:["Then move the GET upwards" srcIndex _ self getUsedGet. dstIndex _ self getUsedGet + nSlots. 1 to: self getUsedGet do:[:i| getBuffer at: (dstIndex _ dstIndex - 1) put: (getBuffer at: (srcIndex _ srcIndex - 1))]. ]. getBuffer _ getBuffer + nSlots. ^true! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 10/29/1998 18:37'!allocateStackEntry: nSlots "AET and Stack allocation are symmetric" ^self needAvailableSpace: nSlots! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 10/30/1998 19:24'!allocateStackFillEntry ^self wbStackPush: self stackFillEntryLength! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 10/30/1998 19:24'!freeStackFillEntry self wbStackPop: self stackFillEntryLength.! !!BalloonEngineBase methodsFor: 'allocating' stamp: 'ar 11/25/1998 02:19'!needAvailableSpace: nSlots "Check if we have n slots available" GWHeaderSize + objUsed + self getUsedGet + self aetUsedGet + nSlots > self wbTopGet ifTrue:[ self stopBecauseOf: GErrorNoMoreSpace. ^false ]. ^true! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 11/1/1998 01:07'!addEdgeToGET: edge self inline: false. (self allocateGETEntry: 1) ifFalse:[^0]. "Install edge in the GET" getBuffer at: self getUsedGet put: edge. self getUsedPut: self getUsedGet + 1.! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 11/25/1998 00:41'!createGlobalEdgeTable "Create the global edge table" | object end | self inline: false. object _ 0. end _ objUsed. [object < end] whileTrue:[ "Note: addEdgeToGET: may fail on insufficient space but that's not a problem here" (self isEdge: object) ifTrue:[ "Check if the edge starts below fillMaxY." (self edgeYValueOf: object) >= self fillMaxYGet ifFalse:[ self checkedAddEdgeToGET: object. ]. ]. object _ object + (self objectLengthOf: object). ].! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 11/9/1998 15:36'!findNextExternalEntryFromGET "Check the global edge table for any entries that cannot be handled by the engine itself. If there are any, return true. Otherwise, initialize the the edge and add it to the AET" | yValue edge type | yValue _ self currentYGet. "As long as we have entries in the GET" [self getStartGet < self getUsedGet] whileTrue:[ edge _ getBuffer at: self getStartGet. (self edgeYValueOf: edge) > yValue ifTrue:[^false]. "No more edges to add" type _ self objectTypeOf: edge. (type bitAnd: GEPrimitiveWideMask) = GEPrimitiveEdge ifTrue:[^true]. "This is an external edge" "Note: We must make sure not to do anything with the edge if there is not enough room in the AET" (self needAvailableSpace: 1) ifFalse:[^false]. "No more room" "Process the edge in the engine itself" self dispatchOn: type in: EdgeInitTable. "Insert the edge into the AET" self insertEdgeIntoAET: edge. self getStartPut: self getStartGet + 1. ]. "No entries in GET" ^false! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 10/28/1998 21:07'!getSorts: edge1 before: edge2 "Return true if the edge at index i should sort before the edge at index j." | diff | self inline: false. edge1 = edge2 ifTrue:[^true]. "First, sort by Y" diff _ (self edgeYValueOf: edge1) - (self edgeYValueOf: edge2). diff = 0 ifFalse:[^diff < 0]. "Then, by X" diff _ (self edgeXValueOf: edge1) - (self edgeXValueOf: edge2). ^diff < 0! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 11/25/1998 00:41'!initializeGETProcessing "Initialization stuff that needs to be done before any processing can take place." self inline: false. "Make sure aaLevel is initialized" self setAALevel: self aaLevelGet. self clipMinXGet < 0 ifTrue:[self clipMinXPut: 0]. self clipMaxXGet > self spanSizeGet ifTrue:[self clipMaxXPut: self spanSizeGet]. "Convert clipRect to aaLevel" self fillMinXPut: self clipMinXGet << self aaShiftGet. self fillMinYPut: self clipMinYGet << self aaShiftGet. self fillMaxXPut: self clipMaxXGet << self aaShiftGet. self fillMaxYPut: self clipMaxYGet << self aaShiftGet. "Reset GET and AET" self getUsedPut: 0. self aetUsedPut: 0. getBuffer _ aetBuffer _ objBuffer + objUsed. "Create the global edge table" self createGlobalEdgeTable. engineStopped ifTrue:[^nil]. self getUsedGet = 0 ifTrue:[ "Nothing to do" self currentYPut: self fillMaxYGet. ^0]. "Sort entries in the GET" self sortGlobalEdgeTable. "Find the first y value to be processed" self currentYPut: (self edgeYValueOf: (getBuffer at: 0)). self currentYGet < self fillMinYGet ifTrue:[self currentYPut: self fillMinYGet]. "Load and clear the span buffer" self spanStartPut: 0. self spanEndPut: (self spanSizeGet << self aaShiftGet) - 1. self clearSpanBuffer. "@@: Is this really necessary?!!"! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 10/27/1998 17:55'!quickSortGlobalEdgeTable: array from: i to: j "Sort elements i through j of self to be nondescending according to sortBlock." "Note: The original loop has been heavily re-written for C translation" | di dij dj tt ij k l n tmp again before | self var: #array declareC:'int *array'. self inline: false. "The prefix d means the data at that index." (n _ j + 1 - i) <= 1 ifTrue: [^0]. "Nothing to sort." "Sort di,dj." di _ array at: i. dj _ array at: j. before _ self getSorts: di before: dj. "i.e., should di precede dj?" before ifFalse:[ tmp _ array at: i. array at: i put: (array at: j). array at: j put: tmp. tt _ di. di _ dj. dj _ tt]. n <= 2 ifTrue:[^0]. "More than two elements." ij _ (i + j) // 2. "ij is the midpoint of i and j." dij _ array at: ij. "Sort di,dij,dj. Make dij be their median." before _ (self getSorts: di before: dij). "i.e. should di precede dij?" before ifTrue:[ before _ (self getSorts: dij before: dj). "i.e., should dij precede dj?" before ifFalse:["i.e., should dij precede dj?" tmp _ array at: j. array at: j put: (array at: ij). array at: ij put: tmp. dij _ dj] ] ifFalse:[ "i.e. di should come after dij" tmp _ array at: i. array at: i put: (array at: ij). array at: ij put: tmp. dij _ di]. n <= 3 ifTrue:[^0]. "More than three elements." "Find k>i and l<j such that dk,dij,dl are in reverse order. Swap k and l. Repeat this procedure until k and l pass each other." k _ i. l _ j. again _ true. [again] whileTrue:[ before _ true. [before] whileTrue:[ k <= (l _ l - 1) ifTrue:[ tmp _ array at: l. before _ self getSorts: dij before: tmp] ifFalse:[before _ false]. ]. before _ true. [before] whileTrue:[ (k _ k + 1) <= l ifTrue:[ tmp _ array at: k. before _ self getSorts: tmp before: dij] ifFalse:[before _ false]]. again _ k <= l. again ifTrue:[ tmp _ array at: k. array at: k put: (array at: l). array at: l put: tmp]]. "Now l<k (either 1 or 2 less), and di through dl are all less than or equal to dk through dj. Sort those two segments." self quickSortGlobalEdgeTable: array from: i to: l. self quickSortGlobalEdgeTable: array from: k to: j.! !!BalloonEngineBase methodsFor: 'GET processing' stamp: 'ar 10/27/1998 23:34'!sortGlobalEdgeTable "Sort the entire global edge table" self quickSortGlobalEdgeTable: getBuffer from: 0 to: self getUsedGet-1.! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 11/24/1998 22:47'!findNextAETEdgeFrom: leftEdge | depth rightEdge | depth _ self edgeZValueOf: leftEdge. [self aetStartGet < self aetUsedGet] whileTrue:[ rightEdge _ aetBuffer at: self aetStartGet. (self edgeZValueOf: rightEdge) >= depth ifTrue:[^rightEdge]. self aetStartPut: self aetStartGet + 1. ]. ^nil! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 11/25/1998 23:21'!findNextExternalFillFromAET "Scan the active edge table. If there is any fill that cannot be handled by the engine itself, return true. Otherwise handle the fills and return false." | leftEdge rightEdge leftX rightX |"self currentYGet >= 680 ifTrue:[self printAET.self halt.]." self inline: false. leftX _ rightX _ self fillMaxXGet. [self aetStartGet < self aetUsedGet] whileTrue:[ leftEdge _ rightEdge _ aetBuffer at: self aetStartGet. "TODO: We should check if leftX from last operation is greater than leftX from next edge. Currently, we rely here on spanEndAA from the span buffer fill." leftX _ rightX _ self edgeXValueOf: leftEdge. leftX >= self fillMaxXGet ifTrue:[^false]. "Nothing more visible" self quickRemoveInvalidFillsAt: leftX. "Check if we need to draw the edge" (self isWide: leftEdge) ifTrue:[ self toggleWideFillOf: leftEdge. "leftX _ rightX _ self drawWideEdge: leftEdge from: leftX." ]. (self areEdgeFillsValid: leftEdge) ifTrue:[ self toggleFillsOf: leftEdge. "Adjust the fills" engineStopped ifTrue:[^false]. ]. self aetStartPut: self aetStartGet + 1. self aetStartGet < self aetUsedGet ifTrue:[ rightEdge _ aetBuffer at: self aetStartGet. rightX _ self edgeXValueOf: rightEdge. rightX >= self fillMinXGet ifTrue:["This is the visible portion" self fillAllFrom: leftX to: rightX. "Fetch the currently active fill" "fill _ self makeUnsignedFrom: self topFill. fill = 0 ifFalse:[self fillSpan: fill from: leftX to: rightX max: self topRightX]" ]. ]. ]. "Note: Due to pre-clipping we may have to draw remaining stuff with the last fill" rightX < self fillMaxXGet ifTrue:[ self fillAllFrom: rightX to: self fillMaxXGet. "fill _ self makeUnsignedFrom: self topFill. fill = 0 ifFalse:[self fillSpan: fill from: rightX to: self fillMaxXGet max: self topRightX]." ]. ^false! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 11/9/1998 15:36'!findNextExternalUpdateFromAET "Check the active edge table for any entries that cannot be handled by the engine itself. If there are any, return true. Otherwise, step the the edge to the next y value." | edge count type | self inline: false. [self aetStartGet < self aetUsedGet] whileTrue:[ edge _ aetBuffer at: self aetStartGet. count _ (self edgeNumLinesOf: edge) - 1. count = 0 ifTrue:[ "Edge at end -- remove it" self removeFirstAETEntry ] ifFalse:[ "Store remaining lines back" self edgeNumLinesOf: edge put: count. type _ self objectTypeOf: edge. (type bitAnd: GEPrimitiveWideMask) = GEPrimitiveEdge ifTrue:[^true]. "This is an external edge" self dispatchOn: type in: EdgeStepTable. self resortFirstAETEntry. self aetStartPut: self aetStartGet+1. ]. ]. ^false! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 10/28/1998 21:07'!indexForInsertingIntoAET: edge "Find insertion point for the given edge in the AET" | initialX index | self inline: false. initialX _ self edgeXValueOf: edge. index _ 0. [index < self aetUsedGet and:[ (self edgeXValueOf: (aetBuffer at: index)) < initialX]] whileTrue:[index _ index + 1]. [index < self aetUsedGet and:[ (self edgeXValueOf: (aetBuffer at: index)) = initialX and:[ (self getSorts: (aetBuffer at: index) before: edge)]]] whileTrue:[index _ index + 1]. ^index! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 10/28/1998 19:52'!insertEdgeIntoAET: edge "Insert the edge with the given index from the global edge table into the active edge table. The edge has already been stepped to the initial yValue -- thus remainingLines and rasterX are both set." | index | self inline: false. "Check for the number of lines remaining" (self edgeNumLinesOf: edge) <= 0 ifTrue:[^nil]. "Nothing to do" "Find insertion point" index _ self indexForInsertingIntoAET: edge. "And insert edge" self insertToAET: edge beforeIndex: index.! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 10/28/1998 21:07'!insertToAET: edge beforeIndex: index "Insert the given edge into the AET." | i | self inline: false. "Make sure we have space in the AET" (self allocateAETEntry: 1) ifFalse:[^nil]. "Insufficient space in AET" i _ self aetUsedGet-1. [i < index] whileFalse:[ aetBuffer at: i+1 put: (aetBuffer at: i). i _ i - 1. ]. aetBuffer at: index put: edge. self aetUsedPut: self aetUsedGet + 1.! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 10/28/1998 01:39'!moveAETEntryFrom: index edge: edge x: xValue "The entry at index is not in the right position of the AET. Move it to the left until the position is okay." | newIndex | self inline: false. newIndex _ index. [newIndex > 0 and:[(self edgeXValueOf: (aetBuffer at: newIndex-1)) > xValue]] whileTrue:[ aetBuffer at: newIndex put: (aetBuffer at: newIndex-1). newIndex _ newIndex - 1]. aetBuffer at: newIndex put: edge.! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 10/28/1998 21:07'!removeFirstAETEntry | index | self inline: false. index _ self aetStartGet. self aetUsedPut: self aetUsedGet - 1. [index < self aetUsedGet] whileTrue:[ aetBuffer at: index put: (aetBuffer at: index + 1). index _ index + 1. ].! !!BalloonEngineBase methodsFor: 'AET processing' stamp: 'ar 10/28/1998 21:07'!resortFirstAETEntry | edge xValue leftEdge | self inline: false. self aetStartGet = 0 ifTrue:[^nil]. "Nothing to resort" edge _ aetBuffer at: self aetStartGet. xValue _ self edgeXValueOf: edge. leftEdge _ aetBuffer at: (self aetStartGet - 1). (self edgeXValueOf: leftEdge) <= xValue ifTrue:[^nil]. "Okay" self moveAETEntryFrom: self aetStartGet edge: edge x: xValue.! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/24/1998 22:42'!fillSorts: fillEntry1 before: fillEntry2 "Return true if fillEntry1 should be drawn before fillEntry2" | diff | self inline: false. "First check the depth value" diff _ (self stackFillDepth: fillEntry1) - (self stackFillDepth: fillEntry2). diff = 0 ifFalse:[^diff > 0]. "See the class comment for aetScanningProblems" ^(self cCoerce: (self makeUnsignedFrom: (self stackFillValue: fillEntry1)) to:'unsigned') < (self cCoerce: (self makeUnsignedFrom: (self stackFillValue: fillEntry2)) to: 'unsigned')! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 15:47'!findStackFill: fillIndex depth: depth | index | index _ 0. [index < self stackFillSize and:[ (self stackFillValue: index) ~= fillIndex or:[ (self stackFillDepth: index) ~= depth]]] whileTrue:[index _ index + self stackFillEntryLength]. index >= self stackFillSize ifTrue:[^-1] ifFalse:[^index].! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 15:48'!hideFill: fillIndex depth: depth "Make the fill style with the given index invisible" | index newTopIndex newTop newDepth newRightX | self inline: false. index _ self findStackFill: fillIndex depth: depth. index = -1 ifTrue:[^false]. index = 0 ifTrue:[ self freeStackFillEntry. ^true]. "Fill is visible - replace it with the last entry on the stack" self stackFillValue: index put: (self stackFillValue: 0). self stackFillDepth: index put: (self stackFillDepth: 0). self stackFillRightX: index put: (self stackFillRightX: 0). self freeStackFillEntry. (self stackFillSize <= self stackFillEntryLength) ifTrue:[^true]. "Done" "Find the new top fill" newTopIndex _ 0. index _ self stackFillEntryLength. [index < self stackFillSize] whileTrue:[ (self fillSorts: index before: newTopIndex) ifTrue:[newTopIndex _ index]. index _ index + self stackFillEntryLength. ]. (newTopIndex + self stackFillEntryLength = self stackFillSize) ifTrue:[^true]. "Top fill not changed" newTop _ self stackFillValue: newTopIndex. self stackFillValue: newTopIndex put: self topFillValue. self topFillValuePut: newTop. newDepth _ self stackFillDepth: newTopIndex. self stackFillDepth: newTopIndex put: self topFillDepth. self topFillDepthPut: newDepth. newRightX _ self stackFillRightX: newTopIndex. self stackFillRightX: newTopIndex put: self topFillRightX. self topFillRightXPut: newRightX. ^true! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 15:16'!quickRemoveInvalidFillsAt: leftX "Remove any top fills if they have become invalid." self stackFillSize = 0 ifTrue:[^nil]. [self topRightX <= leftX] whileTrue:[ self hideFill: self topFill depth: self topDepth. self stackFillSize = 0 ifTrue:[^nil]. ].! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 14:38'!showFill: fillIndex depth: depth rightX: rightX self inline: false. (self allocateStackFillEntry) ifFalse:[^nil]. "Insufficient space" self stackFillValue: 0 put: fillIndex. self stackFillDepth: 0 put: depth. self stackFillRightX: 0 put: rightX. self stackFillSize = self stackFillEntryLength ifTrue:[^nil]. "No need to update" (self fillSorts: 0 before: self stackFillSize - self stackFillEntryLength) ifTrue:[ "New top fill" self stackFillValue: 0 put: self topFillValue. self stackFillDepth: 0 put: self topFillDepth. self stackFillRightX: 0 put: self topFillRightX. self topFillValuePut: fillIndex. self topFillDepthPut: depth. self topFillRightXPut: rightX. ].! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 14:38'!toggleFill: fillIndex depth: depth rightX: rightX "Make the fill style with the given index either visible or invisible" | hidden | self inline: false. self stackFillSize = 0 ifTrue:[ (self allocateStackFillEntry) ifTrue:[ self topFillValuePut: fillIndex. self topFillDepthPut: depth. self topFillRightXPut: rightX. ]. ] ifFalse:[ hidden _ self hideFill: fillIndex depth: depth. hidden ifFalse:[self showFill: fillIndex depth: depth rightX: rightX]. ].! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 15:19'!toggleFillsOf: edge | depth fillIndex | self inline: false. (self needAvailableSpace: self stackFillEntryLength * 2) ifFalse:[^nil]. "Make sure we have enough space left" depth _ (self edgeZValueOf: edge) << 1. fillIndex _ self edgeLeftFillOf: edge. fillIndex = 0 ifFalse:[self toggleFill: fillIndex depth: depth rightX: 999999999]. fillIndex _ self edgeRightFillOf: edge. fillIndex = 0 ifFalse:[self toggleFill: fillIndex depth: depth rightX: 999999999]. self quickRemoveInvalidFillsAt: (self edgeXValueOf: edge).! !!BalloonEngineBase methodsFor: 'FILL processing' stamp: 'ar 11/25/1998 15:50'!toggleWideFillOf: edge | fill type lineWidth depth rightX index | self inline: false. type _ self edgeTypeOf: edge. dispatchedValue _ edge. self dispatchOn: type in: WideLineWidthTable. lineWidth _ dispatchReturnValue. self dispatchOn: type in: WideLineFillTable. fill _ dispatchReturnValue. fill = 0 ifTrue:[^nil]. (self needAvailableSpace: self stackFillEntryLength) ifFalse:[^nil]. "Make sure we have enough space left" depth _ (self edgeZValueOf: edge) << 1 + 1. "So lines sort before interior fills" rightX _ (self edgeXValueOf: edge) + lineWidth. index _ self findStackFill: fill depth: depth. index = -1 ifTrue:[ self showFill: fill depth: depth rightX: rightX. ] ifFalse:[ (self stackFillRightX: index) < rightX ifTrue:[self stackFillRightX: index put: rightX]. ]. self quickRemoveInvalidFillsAt: (self edgeXValueOf: edge).! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/9/1998 00:53'!aaFirstPixelFrom: leftX to: rightX "Common function to compute the first full pixel for AA drawing" | firstPixel | self inline: true. firstPixel _ (leftX + self aaLevelGet - 1) bitAnd: (self aaLevelGet - 1) bitInvert32. firstPixel > rightX ifTrue:[^rightX] ifFalse:[^firstPixel]! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/9/1998 00:53'!aaLastPixelFrom: leftX to: rightX "Common function to compute the last full pixel for AA drawing" self inline: true. ^(rightX - 1) bitAnd: (self aaLevelGet - 1) bitInvert32.! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/9/1998 00:50'!adjustAALevel "NOTE: This method is (hopefully) obsolete due to unrolling the fill loops to deal with full pixels." "Adjust the span buffers values by the appropriate color offset for anti-aliasing. We do this by replicating the top bits of each color in the lower bits. The idea is that we can scale each color value uniquely from 0 to 255 and thus fill the entire range of colors." | adjustShift adjustMask x0 x1 pixelValue | self inline: false. adjustShift _ 8 - self aaColorShiftGet. adjustMask _ self aaColorMaskGet bitInvert32. x0 _ self spanStartGet >> self aaShiftGet. x1 _ self spanEndGet >> self aaShiftGet. [x0 < x1] whileTrue:[ pixelValue _ spanBuffer at: x0. spanBuffer at: x0 put: (pixelValue bitOr: (pixelValue >> adjustShift bitAnd: adjustMask)). x0 _ x0 + 1].! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/14/1998 19:31'!clearSpanBuffer "Clear the current span buffer. The span buffer is only cleared in the area that has been used by the previous scan line." | x0 x1 | self inline: false. x0 _ self spanStartGet >> self aaShiftGet. x1 _ self spanEndGet >> self aaShiftGet + 1. x0 < 0 ifTrue:[x0 _ 0]. x1 > self spanSizeGet ifTrue:[x1 _ self spanSizeGet]. [x0 < x1] whileTrue:[ spanBuffer at: x0 put: 0. x0 _ x0 + 1]. self spanStartPut: self spanSizeGet. self spanEndPut: 0.! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 5/12/2000 16:42'!displaySpanBufferAt: y "Display the span buffer at the current scan line." | targetX0 targetX1 targetY | self inline: false. "self aaLevelGet > 1 ifTrue:[self adjustAALevel]." targetX0 _ self spanStartGet >> self aaShiftGet. targetX0 < self clipMinXGet ifTrue:[targetX0 _ self clipMinXGet]. targetX1 _ (self spanEndGet + self aaLevelGet - 1) >> self aaShiftGet. targetX1 > self clipMaxXGet ifTrue:[targetX1 _ self clipMaxXGet]. targetY _ y >> self aaShiftGet. (targetY < self clipMinYGet or:[targetY >= self clipMaxYGet or:[ targetX1 < self clipMinXGet or:[targetX0 >= self clipMaxXGet]]]) ifTrue:[^0]. self copyBitsFrom: targetX0 to: targetX1 at: targetY.! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/25/1998 02:34'!drawWideEdge: edge from: leftX "Draw the given edge starting from leftX with the edge's fill. Return the end value of the drawing operation." | rightX fill type lineWidth | self inline: false. "Not for the moment" type _ self edgeTypeOf: edge. dispatchedValue _ edge. self dispatchOn: type in: WideLineWidthTable. lineWidth _ dispatchReturnValue. self dispatchOn: type in: WideLineFillTable. fill _ self makeUnsignedFrom: dispatchReturnValue. fill = 0 ifTrue:[^leftX]. "Check if this line is only partially visible" "self assert:(self isFillColor: fill)." rightX _ leftX + lineWidth. self fillSpan: fill from: leftX to: rightX. ^rightX! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/25/1998 15:12'!fillAllFrom: leftX to: rightX "Fill the span buffer from leftX to rightX with the given fill." | fill startX stopX | self inline: true. fill _ self topFill. startX _ leftX. stopX _ self topRightX. [stopX < rightX] whileTrue:[ fill _ self makeUnsignedFrom: self topFill. fill = 0 ifFalse:[ (self fillSpan: fill from: startX to: stopX) ifTrue:[^true]]. self quickRemoveInvalidFillsAt: stopX. startX _ stopX. stopX _ self topRightX]. fill _ self makeUnsignedFrom: self topFill. fill = 0 ifFalse:[^self fillSpan: fill from: startX to: rightX]. ^false! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/9/1998 16:10'!fillBitmapSpan: bits from: leftX to: rightX "Fill the span buffer between leftEdge and rightEdge using the given bits. Note: We always start from zero - this avoids using huge bitmap buffers if the bitmap is to be displayed at the very far right hand side and also gives us a chance of using certain bitmaps (e.g., those with depth 32) directly." | x0 x1 x bitX colorMask colorShift baseShift fillValue | self inline: false. self var: #bits declareC:'int *bits'. x0 _ leftX. x1 _ rightX. bitX _ -1. "Hack for pre-increment" self aaLevelGet = 1 ifTrue:["Speedy version for no anti-aliasing" [x0 < x1] whileTrue:[ fillValue _ (self cCoerce: bits to: 'int *') at: (bitX _ bitX + 1). spanBuffer at: x0 put: fillValue. x0 _ x0 + 1. ]. ] ifFalse:["Generic version with anti-aliasing" colorMask _ self aaColorMaskGet. colorShift _ self aaColorShiftGet. baseShift _ self aaShiftGet. [x0 < x1] whileTrue:[ x _ x0 >> baseShift. fillValue _ (self cCoerce: bits to: 'int *') at: (bitX _ bitX + 1). fillValue _ (fillValue bitAnd: colorMask) >> colorShift. spanBuffer at: x put: (spanBuffer at: x) + fillValue. x0 _ x0 + 1. ]. ]. x1 > self spanEndGet ifTrue:[self spanEndPut: x1]. x1 > self spanEndAAGet ifTrue:[self spanEndAAPut: x1].! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/8/1998 03:30'!fillColorSpan: pixelValue32 from: leftX to: rightX "Fill the span buffer between leftEdge and rightEdge with the given pixel value." | x0 x1 | self inline: true. "Use a unrolled version for anti-aliased fills..." self aaLevelGet = 1 ifFalse:[^self fillColorSpanAA: pixelValue32 x0: leftX x1: rightX]. x0 _ leftX. x1 _ rightX. "Unroll the inner loop four times, since we're only storing data." [x0 + 4 < x1] whileTrue:[ spanBuffer at: x0 put: pixelValue32. spanBuffer at: x0+1 put: pixelValue32. spanBuffer at: x0+2 put: pixelValue32. spanBuffer at: x0+3 put: pixelValue32. x0 _ x0+4. ]. [x0 < x1] whileTrue:[ spanBuffer at: x0 put: pixelValue32. x0 _ x0 + 1. ].! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/9/1998 00:52'!fillColorSpanAA: pixelValue32 x0: leftX x1: rightX "This is the inner loop for solid color fills with anti-aliasing. This loop has been unrolled for speed and quality into three parts: a) copy all pixels that fall into the first full pixel. b) copy aaLevel pixels between the first and the last full pixel c) copy all pixels that fall in the last full pixel" | colorMask baseShift x idx firstPixel lastPixel aaLevel pv32 | self inline: false. "Not now -- maybe later" "Compute the pixel boundaries." firstPixel _ self aaFirstPixelFrom: leftX to: rightX. lastPixel _ self aaLastPixelFrom: leftX to: rightX. aaLevel _ self aaLevelGet. baseShift _ self aaShiftGet. x _ leftX. "Part a: Deal with the first n sub-pixels" x < firstPixel ifTrue:[ pv32 _ (pixelValue32 bitAnd: self aaColorMaskGet) >> self aaColorShiftGet. [x < firstPixel] whileTrue:[ idx _ x >> baseShift. spanBuffer at: idx put: (spanBuffer at: idx) + pv32. x _ x + 1. ]. ]. "Part b: Deal with the full pixels" x < lastPixel ifTrue:[ colorMask _ (self aaColorMaskGet >> self aaShiftGet) bitOr: 16rF0F0F0F0. pv32 _ (pixelValue32 bitAnd: colorMask) >> self aaShiftGet. [x < lastPixel] whileTrue:[ idx _ x >> baseShift. spanBuffer at: idx put: (spanBuffer at: idx) + pv32. x _ x + aaLevel. ]. ]. "Part c: Deal with the last n sub-pixels" x < rightX ifTrue:[ pv32 _ (pixelValue32 bitAnd: self aaColorMaskGet) >> self aaColorShiftGet. [x < rightX] whileTrue:[ idx _ x >> baseShift. spanBuffer at: idx put: (spanBuffer at: idx) + pv32. x _ x + 1. ]. ].! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/15/1998 02:04'!fillSpan: fill from: leftX to: rightX "Fill the span buffer from leftX to rightX with the given fill. Clip before performing any operations. Return true if the fill must be handled by some Smalltalk code." | x0 x1 type | self inline: false. fill = 0 ifTrue:[^false]. "Nothing to do" "Start from spEnd - we must not paint pixels twice at a scan line" leftX < self spanEndAAGet ifTrue:[x0 _ self spanEndAAGet] ifFalse:[x0 _ leftX]. rightX > (self spanSizeGet << self aaShiftGet) ifTrue:[x1 _ (self spanSizeGet << self aaShiftGet)] ifFalse:[x1 _ rightX]. "Clip left and right values" x0 < self fillMinXGet ifTrue:[x0 _ self fillMinXGet]. x1 > self fillMaxXGet ifTrue:[x1 _ self fillMaxXGet]. "Adjust start and end values of span" x0 < self spanStartGet ifTrue:[self spanStartPut: x0]. x1 > self spanEndGet ifTrue:[self spanEndPut: x1]. x1 > self spanEndAAGet ifTrue:[self spanEndAAPut: x1]. x0 >= x1 ifTrue:[^false]. "Nothing to do" (self isFillColor: fill) ifTrue:[ self fillColorSpan: fill from: x0 to: x1. ] ifFalse:[ "Store the values for the dispatch" self lastExportedFillPut: fill. self lastExportedLeftXPut: x0. self lastExportedRightXPut: x1. type _ self fillTypeOf: fill. type <= 1 ifTrue:[^true]. self dispatchOn: type in: FillTable. ]. ^false! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/25/1998 14:57'!fillSpan: fill from: leftX to: rightX max: maxRightX "Fill the span buffer from leftX to rightX with the given fill. Clip before performing any operations. Return true if the fill must be handled by some Smalltalk code." | x0 x1 type | self inline: false. fill = 0 ifTrue:[^false]. "Nothing to do" "Start from spEnd - we must not paint pixels twice at a scan line" leftX < self spanEndAAGet ifTrue:[x0 _ self spanEndAAGet] ifFalse:[x0 _ leftX]. rightX > (self spanSizeGet << self aaShiftGet) ifTrue:[x1 _ (self spanSizeGet << self aaShiftGet)] ifFalse:[x1 _ rightX]. maxRightX < x1 ifTrue:[x1 _ maxRightX]. "Clip left and right values" x0 < self fillMinXGet ifTrue:[x0 _ self fillMinXGet]. x1 > self fillMaxXGet ifTrue:[x1 _ self fillMaxXGet]. "Adjust start and end values of span" x0 < self spanStartGet ifTrue:[self spanStartPut: x0]. x1 > self spanEndGet ifTrue:[self spanEndPut: x1]. x1 > self spanEndAAGet ifTrue:[self spanEndAAPut: x1]. x0 >= x1 ifTrue:[^false]. "Nothing to do" (self isFillColor: fill) ifTrue:[ self fillColorSpan: fill from: x0 to: x1. ] ifFalse:[ "Store the values for the dispatch" self lastExportedFillPut: fill. self lastExportedLeftXPut: x0. self lastExportedRightXPut: x1. type _ self fillTypeOf: fill. type <= 1 ifTrue:[^true]. self dispatchOn: type in: FillTable. ]. ^false! !!BalloonEngineBase methodsFor: 'displaying' stamp: 'ar 11/8/1998 15:13'!postDisplayAction "We have just blitted a scan line to the screen. Do whatever seems to be a good idea here." "Note: In the future we may check the time needed for this scan line and interrupt processing to give the Smalltalk code a chance to run at a certain time." self inline: false. "Check if there is any more work to do." (self getStartGet >= self getUsedGet and:[self aetUsedGet = 0]) ifTrue:[ "No more entries to process" self statePut: GEStateCompleted. ]. (self currentYGet >= self fillMaxYGet) ifTrue:[ "Out of clipping range" self statePut: GEStateCompleted. ].! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 11/8/1998 14:26'!incrementPoint: point by: delta self var: #point declareC:'int *point'. point at: 0 put: (point at: 0) + delta. point at: 1 put: (point at: 1) + delta.! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 9/5/1999 14:13'!transformColor: fillIndex | r g b a transform alphaScale | self var: #transform declareC:'float *transform'. self var: #alphaScale declareC:'double alphaScale'. (fillIndex = 0 or:[self isFillColor: fillIndex]) ifFalse:[^fillIndex]. b _ fillIndex bitAnd: 255. g _ (fillIndex >> 8) bitAnd: 255. r _ (fillIndex >> 16) bitAnd: 255. a _ (fillIndex >> 24) bitAnd: 255. (self hasColorTransform) ifTrue:[ transform _ self colorTransform. alphaScale _ (a * (transform at: 6) + (transform at: 7)) / a. r _ (r * (transform at: 0) + (transform at: 1) * alphaScale) asInteger. g _ (g * (transform at: 2) + (transform at: 3) * alphaScale) asInteger. b _ (b * (transform at: 4) + (transform at: 5) * alphaScale) asInteger. a _ a * alphaScale. r _ r max: 0. r _ r min: 255. g _ g max: 0. g _ g min: 255. b _ b max: 0. b _ b min: 255. a _ a max: 0. a _ a min: 255. ]. a < 1 ifTrue:[^0]."ALWAYS return zero for transparent fills" "If alpha is not 255 (or close thereto) then we need to flush the engine before proceeding" (a < 255 and:[self needsFlush]) ifTrue:[self stopBecauseOf: GErrorNeedFlush]. ^b + (g << 8) + (r << 16) + (a << 24)! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 11/24/1998 19:47'!transformPoint: point "Transform the given point. If haveMatrix is true then use the current transformation." self var:#point declareC:'int *point'. self hasEdgeTransform ifFalse:[ "Multiply each component by aaLevel and add a half pixel" point at: 0 put: (point at: 0) + self destOffsetXGet * self aaLevelGet. point at: 1 put: (point at: 1) + self destOffsetYGet * self aaLevelGet. ] ifTrue:[ "Note: AA adjustment is done in #transformPoint: for higher accuracy" self transformPoint: point into: point. ].! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 11/1/1998 16:59'!transformPoint: srcPoint into: dstPoint "Transform srcPoint into dstPoint by using the currently loaded matrix" "Note: This method has been rewritten so that inlining works (e.g., removing the declarations and adding argument coercions at the appropriate points)" self inline: true. self transformPointX: ((self cCoerce: srcPoint to: 'int *') at: 0) asFloat y: ((self cCoerce: srcPoint to:'int *') at: 1) asFloat into: (self cCoerce: dstPoint to: 'int *')! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 11/24/1998 19:25'!transformPointX: xValue y: yValue into: dstPoint "Transform srcPoint into dstPoint by using the currently loaded matrix" "Note: This should be rewritten so that inlining works (e.g., removing the declarations and adding argument coercions at the appropriate points)" | x y transform | self inline: true. "Won't help at the moment ;-(" self var: #dstPoint declareC:'int *dstPoint'. self var: #xValue declareC: 'double xValue'. self var: #yValue declareC: 'double yValue'. self var: #transform declareC:'float *transform'. transform _ self edgeTransform. x _ ((((transform at: 0) * xValue) + ((transform at: 1) * yValue) + (transform at: 2)) * self aaLevelGet asFloat) asInteger. y _ ((((transform at: 3) * xValue) + ((transform at: 4) * yValue) + (transform at: 5)) * self aaLevelGet asFloat) asInteger. dstPoint at: 0 put: x. dstPoint at: 1 put: y.! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 11/24/1998 19:48'!transformPoints: n "Transform n (n=1,2,3) points. If haveMatrix is true then the matrix contains the actual transformation." self inline: true. n > 0 ifTrue:[self transformPoint: self point1Get]. n > 1 ifTrue:[self transformPoint: self point2Get]. n > 2 ifTrue:[self transformPoint: self point3Get]. n > 3 ifTrue:[self transformPoint: self point4Get].! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 10/25/1999 00:57'!transformWidth: w "Transform the given width" | deltaX deltaY dstWidth dstWidth2 | self inline: false. self var: #deltaX declareC:'double deltaX'. self var: #deltaY declareC:'double deltaY'. w = 0 ifTrue:[^0]. self point1Get at: 0 put: 0. self point1Get at: 1 put: 0. self point2Get at: 0 put: w * 256. self point2Get at: 1 put: 0. self point3Get at: 0 put: 0. self point3Get at: 1 put: w * 256. self transformPoints: 3. deltaX _ ((self point2Get at: 0) - (self point1Get at: 0)) asFloat. deltaY _ ((self point2Get at: 1) - (self point1Get at: 1)) asFloat. dstWidth _ (((deltaX * deltaX) + (deltaY * deltaY)) sqrt asInteger + 128) // 256. deltaX _ ((self point3Get at: 0) - (self point1Get at: 0)) asFloat. deltaY _ ((self point3Get at: 1) - (self point1Get at: 1)) asFloat. dstWidth2 _ (((deltaX * deltaX) + (deltaY * deltaY)) sqrt asInteger + 128) // 256. dstWidth2 < dstWidth ifTrue:[dstWidth _ dstWidth2]. dstWidth = 0 ifTrue:[^1] ifFalse:[^dstWidth]! !!BalloonEngineBase methodsFor: 'transforming' stamp: 'ar 11/25/1998 21:33'!uncheckedTransformColor: fillIndex | r g b a transform | self var: #transform declareC:'float *transform'. (self hasColorTransform) ifFalse:[^fillIndex]. b _ fillIndex bitAnd: 255. g _ (fillIndex >> 8) bitAnd: 255. r _ (fillIndex >> 16) bitAnd: 255. a _ (fillIndex >> 24) bitAnd: 255. transform _ self colorTransform. r _ (r * (transform at: 0) + (transform at: 1)) asInteger. g _ (g * (transform at: 2) + (transform at: 3)) asInteger. b _ (b * (transform at: 4) + (transform at: 5)) asInteger. a _ (a * (transform at: 6) + (transform at: 7)) asInteger. r _ r max: 0. r _ r min: 255. g _ g max: 0. g _ g min: 255. b _ b max: 0. b _ b min: 255. a _ a max: 0. a _ a min: 255. a < 16 ifTrue:[^0]."ALWAYS return zero for transparent fills" ^b + (g << 8) + (r << 16) + (a << 24)! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/9/1998 02:06'!accurateLengthOf: deltaX with: deltaY "Return the accurate length of the vector described by deltaX and deltaY" | length2 | deltaX = 0 ifTrue:[deltaY < 0 ifTrue:[^0-deltaY] ifFalse:[^deltaY]]. deltaY = 0 ifTrue:[deltaX < 0 ifTrue:[^0-deltaX] ifFalse:[^deltaX]]. length2 _ (deltaX * deltaX) + (deltaY * deltaY). ^self computeSqrt: length2! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/7/1998 14:26'!computeSqrt: length2 length2 < 32 ifTrue:[^self smallSqrtTable at: length2] ifFalse:[^(length2 asFloat sqrt + 0.5) asInteger]! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/8/1998 14:33'!estimatedLengthOf: deltaX with: deltaY "Estimate the length of the vector described by deltaX and deltaY. This method may be extremely inaccurate - use it only if you know exactly that this doesn't matter. Otherwise use #accurateLengthOf:width:" | absDx absDy | deltaX >= 0 ifTrue:[absDx _ deltaX] ifFalse:[absDx _ 0 - deltaX]. deltaY >= 0 ifTrue:[absDy _ deltaY] ifFalse:[absDy _ 0 - deltaY]. absDx > absDy ifTrue:[^absDx + (absDy // 2)] ifFalse:[^absDy + (absDx // 2)]! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/24/1998 19:45'!initColorTransform | transform | self inline: false. self var: #transform declareC:'float *transform'. transform _ self colorTransform. transform at: 0 put: (self cCoerce: 1.0 to: 'float'). transform at: 1 put: (self cCoerce: 0.0 to: 'float'). transform at: 2 put: (self cCoerce: 1.0 to: 'float'). transform at: 3 put: (self cCoerce: 0.0 to: 'float'). transform at: 4 put: (self cCoerce: 1.0 to: 'float'). transform at: 5 put: (self cCoerce: 0.0 to: 'float'). transform at: 6 put: (self cCoerce: 1.0 to: 'float'). transform at: 7 put: (self cCoerce: 0.0 to: 'float'). self hasColorTransformPut: 0.! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/24/1998 19:45'!initEdgeTransform | transform | self inline: false. self var: #transform declareC:'float *transform'. transform _ self edgeTransform. transform at: 0 put: (self cCoerce: 1.0 to: 'float'). transform at: 1 put: (self cCoerce: 0.0 to: 'float'). transform at: 2 put: (self cCoerce: 0.0 to: 'float'). transform at: 3 put: (self cCoerce: 0.0 to: 'float'). transform at: 4 put: (self cCoerce: 1.0 to: 'float'). transform at: 5 put: (self cCoerce: 0.0 to: 'float'). self hasEdgeTransformPut: 0.! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/7/1998 14:26'!resetGraphicsEngineStats self inline: false. workBuffer at: GWTimeInitializing put: 0. workBuffer at: GWTimeFinishTest put: 0. workBuffer at: GWTimeNextGETEntry put: 0. workBuffer at: GWTimeAddAETEntry put: 0. workBuffer at: GWTimeNextFillEntry put: 0. workBuffer at: GWTimeMergeFill put: 0. workBuffer at: GWTimeDisplaySpan put: 0. workBuffer at: GWTimeNextAETEntry put: 0. workBuffer at: GWTimeChangeAETEntry put: 0. workBuffer at: GWCountInitializing put: 0. workBuffer at: GWCountFinishTest put: 0. workBuffer at: GWCountNextGETEntry put: 0. workBuffer at: GWCountAddAETEntry put: 0. workBuffer at: GWCountNextFillEntry put: 0. workBuffer at: GWCountMergeFill put: 0. workBuffer at: GWCountDisplaySpan put: 0. workBuffer at: GWCountNextAETEntry put: 0. workBuffer at: GWCountChangeAETEntry put: 0. workBuffer at: GWBezierMonotonSubdivisions put: 0. workBuffer at: GWBezierHeightSubdivisions put: 0. workBuffer at: GWBezierOverflowSubdivisions put: 0. workBuffer at: GWBezierLineConversions put: 0.! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/7/1998 14:26'!setAALevel: level "Set the anti-aliasing level. Three levels are supported: 1 - No antialiasing 2 - 2x2 unweighted anti-aliasing 4 - 4x4 unweighted anti-aliasing. " | aaLevel | self inline: false. level >= 4 ifTrue:[aaLevel _ 4]. (level >= 2) & (level < 4) ifTrue:[aaLevel _ 2]. level < 2 ifTrue:[aaLevel _ 1]. self aaLevelPut: aaLevel. aaLevel = 1 ifTrue:[ self aaShiftPut: 0. self aaColorMaskPut: 16rFFFFFFFF. self aaScanMaskPut: 0. ]. aaLevel = 2 ifTrue:[ self aaShiftPut: 1. self aaColorMaskPut: 16rFCFCFCFC. self aaScanMaskPut: 1. ]. aaLevel = 4 ifTrue:[ self aaShiftPut: 2. self aaColorMaskPut: 16rF0F0F0F0. self aaScanMaskPut: 3. ]. self aaColorShiftPut: self aaShiftGet * 2. self aaHalfPixelPut: self aaShiftGet.! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/8/1998 15:25'!smallSqrtTable | theTable | self inline: false. self returnTypeC:'int *'. self var: #theTable declareC:'static int theTable[32] = {0, 1, 1, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 5, 5, 5, 5, 5, 6}'. ^theTable! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/8/1998 20:57'!squaredLengthOf: deltaX with: deltaY ^(deltaX * deltaX) + (deltaY * deltaY)! !!BalloonEngineBase methodsFor: 'other' stamp: 'ar 11/25/1998 02:22'!stopBecauseOf: stopReason self stopReasonPut: stopReason. engineStopped _ true.! !!BalloonEngineBase methodsFor: 'private' stamp: 'ar 5/16/2000 17:09'!copyBitsFrom: x0 to: x1 at: yValue copyBitsFn = 0 ifTrue:[ "We need copyBits here so try to load it implicitly" self initialiseModule ifFalse:[^false]. ]. ^self cCode:' ((int (*) (int, int, int)) copyBitsFn)(x0, x1, yValue)'! !!BalloonEngineBase methodsFor: 'private' stamp: 'ar 5/13/2000 14:55'!errorWrongIndex "Ignore dispatch errors when translating to C (since we have no entry point for #error in the VM proxy)" self cCode:'' inSmalltalk:[self error:'BalloonEngine: Fatal dispatch error']! !!BalloonEngineBase methodsFor: 'private' stamp: 'ar 5/16/2000 17:08'!loadBitBltFrom: bbObj loadBBFn = 0 ifTrue:[ "We need copyBits here so try to load it implicitly" self initialiseModule ifFalse:[^false]. ]. ^self cCode: '((int (*) (int))loadBBFn)(bbObj)'! !!BalloonEngineBase methodsFor: 'private' stamp: 'ar 10/28/1998 20:58'!makeUnsignedFrom: someIntegerValue ^someIntegerValue! !!BalloonEngineBase methodsFor: 'initialize-release' stamp: 'ar 5/16/2000 19:56'!initialiseModule self export: true. loadBBFn _ interpreterProxy ioLoadFunction: 'loadBitBltFrom' From: bbPluginName. copyBitsFn _ interpreterProxy ioLoadFunction: 'copyBitsFromtoat' From: bbPluginName. ^(loadBBFn ~= 0 and:[copyBitsFn ~= 0])! !!BalloonEngineBase methodsFor: 'initialize-release' stamp: 'ar 5/16/2000 19:57'!moduleUnloaded: aModuleName "The module with the given name was just unloaded. Make sure we have no dangling references." self export: true. self var: #aModuleName type: 'char *'. (aModuleName strcmp: bbPluginName) = 0 ifTrue:[ "BitBlt just shut down. How nasty." loadBBFn _ 0. copyBitsFn _ 0. ].! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 5/16/2000 20:03'!declareCVarsIn: cg "Buffers" cg var: #workBuffer type: #'int*'. cg var: #objBuffer type: #'int*'. cg var: #getBuffer type: #'int*'. cg var: #aetBuffer type: #'int*'. cg var: #spanBuffer type: #'unsigned int*'. cg var: #edgeTransform declareC: 'float edgeTransform[6]'. cg var: #doProfileStats declareC: 'int doProfileStats = 0'. cg var: 'bbPluginName' declareC:'char bbPluginName[256] = "BitBltPlugin"'.! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 11/7/1998 22:26'!initialize "BalloonEngineBase initialize" "BalloonEnginePlugin translateDoInlining: true." EdgeInitTable _ self initializeEdgeInitTable. EdgeStepTable _ self initializeEdgeStepTable. WideLineWidthTable _ self initializeWideLineWidthTable. WideLineFillTable _ self initializeWideLineFillTable. FillTable _ self initializeFillTable.! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 11/4/1998 21:52'!initializeEdgeInitTable "BalloonEngineBase initialize" ^#( errorWrongIndex errorWrongIndex errorWrongIndex errorWrongIndex stepToFirstLine stepToFirstWideLine stepToFirstBezier stepToFirstWideBezier )! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 11/4/1998 21:52'!initializeEdgeStepTable "BalloonEngineBase initialize" ^#( errorWrongIndex errorWrongIndex errorWrongIndex errorWrongIndex stepToNextLine stepToNextWideLine stepToNextBezier stepToNextWideBezier )! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 11/25/1998 19:46'!initializeFillTable "BalloonEngineBase initialize" ^#( errorWrongIndex "Type zero - undefined" errorWrongIndex "Type one - external fill" fillLinearGradient "Linear gradient fill" fillRadialGradient "Radial gradient fill" fillBitmapSpan "Clipped bitmap fill" fillBitmapSpan "Repeated bitmap fill" )! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 11/4/1998 23:03'!initializeWideLineFillTable "BalloonEngineBase initialize" ^#( errorWrongIndex errorWrongIndex returnWideLineFill returnWideBezierFill )! !!BalloonEngineBase class methodsFor: 'class initialization' stamp: 'ar 11/4/1998 23:03'!initializeWideLineWidthTable "BalloonEngineBase initialize" ^#( errorWrongIndex errorWrongIndex returnWideLineWidth returnWideBezierWidth )! !!BalloonEngineBase class methodsFor: 'accessing' stamp: 'ar 5/11/2000 23:48'!moduleName ^'B2DPlugin'! !!BalloonEngineBase class methodsFor: 'accessing' stamp: 'ar 11/11/1998 21:56'!simulatorClass ^BalloonEngineSimulation! !!BalloonEngineBase class methodsFor: 'documentation' stamp: 'ar 11/7/1998 03:33'!a1EngineOutline "The following is a brief outline on how the engine works. In general, we're using a pretty straight-forward active edge approach, e.g., we classify all edges into three different states: a) Waiting for processing b) Active (e.g., being processed) c) Finished Before the engine starts all edges are sorted by their y-value in a so-called 'global edge table' (furthermore referred to as GET) and processed in top to bottom order (the edges are also sorted by x-value but this is only for simplifying the insertion when adding edges). Then, we start at the first visible scan line and execute the following steps: 1) Move all edges starting at the current scan line from state a) to state b) This step requires the GET to be sorted so that we only need to check the first edges of the GET. After the initial state of the edge (e.g., it's current pixel value and data required for incremental updates) the edges are then inserted in the 'active edge table' (called AET). The sort order in the AET is defined by the pixel position of each edge at the current scan line and thus edges are kept in increasing x-order. This step does occur for every edge only once and is therefore not the most time-critical part of the approach. 2) Draw the current scan line This step includes two sub-parts. In the first part, the scan line is assembled. This involves walking through the AET and drawing the pixels between each two neighbour edges. Since each edge can have two associated fills (a 'left' and a 'right' fill) we need to make sure that edges falling on the same pixel position do not affect the painted image. This issue is discussed in the aetScanningProblems documentation. Wide edges (e.g., edges having an associated width) are also handled during this step. Wide edges are always preferred over interior fills - this ensures that the outline of an object cannot be overdrawn by any interior fill of a shape that ends very close to the edge (for more information see wideEdges documentation). After the scan is assembled it is blitted to the screen. This only happens all 'aaLevel' scan lines (for further information see the antiAliasing documentation). This second step is done at each scan line in the image, and is usually the most time-critical part. 3) Update all currently active edges Updating the active edges basically means either to remove the edge from the AET (if it is at the end y value) or incrementally computing the pixel value for the next scan line. Based on the information gathered in the first step, this part should be executed as fast as possible - it happens for each edge in the AET at each scan line and may be the bottleneck if many edges are involved in the drawing operations (see the TODO list; part of it probably deals with the issue)." ^self error:'Comment only'! !!BalloonEngineBase class methodsFor: 'documentation' stamp: 'ar 11/7/1998 03:55'!a2AntiAliasing "The engine currently used a very simple, but efficient anti-aliasing scheme. It is based on a square unweighted filter of size 1, 2, or 4 resulting in three levels of anti-aliasing: * No anti-aliasing (filter size 1) This simply draws each pixel 'as is' on the screen * Slight anti-aliasing (filter size 2) Doubles the rasterization size in each direction and assembles the pixel value as the medium of the four sub-pixels falling into the full pixel * Full anti-aliasing (filter size 4) Quadruples the rasterization in each direction and assembles the pixel value as the medium of the sixteen sub-pixels falling into the full pixelThe reason for using these three AA levels is simply efficiency of computing. Since the above filters (1x1, 2x2, 4x4) have all power of two elements (1, 4, and 16) we can compute the weighted sum of the final pixel by computing destColor _ destColor + (srcColor // subPixels)And, since we're only working on 32bit destination buffer we do not need to compute the components of each color separately but can neatly put the entire color into a single formula: destPixel32 _ destPixel32 + ((srcPixel32 bitAnd: aaMask) >> aaShift).with aaMask = 16rFFFFFFFF for aaLevel = 1, aaMask = 16rFCFCFCFC for aaLevel = 2, aaMask = 16rF0F0F0F0 for aaLevel = 4 and aaShift = 0, 2, or 4 for the different levels. However, while the above is efficient to compute, it also drops accuracy. So, for the 4x4 anti-aliasing we're effectively only using the high 4 bits of each color component. While is generally not a problem (we add 16 sub-pixels into this value) there is a simple arithmetic difficulty because the above cannot fill the entire range of values, e.g., 16 * (255 // 16) = 16 * 15 = 240and not 255 as expected. We solve this problem by replicating the top n (n=0, 2, 4) bits of each component as the low bits in an adjustment step before blitting to scan line to the screen. This has the nice effect that a zero pixel value (e.g., transparent) will remain zero, a white pixel (as computed above) will result in a value of 255 for each component (defining opaque white) and each color inbetween linearly mapped between 0 and 255. " ^self error:'Comment only'! !!BalloonEngineBase class methodsFor: 'documentation' stamp: 'ar 11/7/1998 03:35'!a3RasterizationRules ^self error:'Comment only'! !!BalloonEngineBase class methodsFor: 'documentation' stamp: 'ar 11/7/1998 03:35'!a4WideEdges! !!BalloonEngineBase class methodsFor: 'documentation' stamp: 'ar 11/7/1998 03:36'!a5AETScanningProblems "Due to having two fill entries (one left and one right) there can be problems while scanning the active edge table. In general, the AET should look like the following (ri - regions, ei - edges, fi - fills): | \ | r1 | r2 \ r3 | r4 | \ | e1 e2 e3 with: f(r1) = fLeft(e1) = 0 (empty fill, denoted -) f(r2) = fRight(e1) = fLeft(e2) (denoted x) f(r3) = fRight(e2) = fLeft(e3) (denoted o) f(r4) = fRight(e3) = 0 However, due to integer arithmetic used during computations the AET may look like the following: X \| | | \ | | \ | r1 | r2 \ r3 | r4 | \ | e1 e2 e3 In this case, the starting point of e1 and e2 have the same x value at the first scan line but e2 has been sorted before e1 (Note: This can happen in *many* cases - the above is just a very simple example). Given the above outlined fill relations we have a problem. So, for instance, using the left/right fills as defined by the edges would lead to the effect that in the first scan line region r3 is actually filled with the right fill of e1 while it should actually be filled with the right fill of e2. This leads to noticable artifacts in the image and increasing resolution does not help. What we do here is defining an arbitrary sort order between fills (you can think of it as a depth value but the only thing that matters is that you can order the fills by this number and that the empty fill is always sorted at the end), and toggle the fills between an 'active' and an 'inactive' state at each edge. This is done as follows: For each edge ei in the AET do: * if fLeft(ei) isActive then removeActive(fLeft(ei)) else addActive(fLeft(ei)) * if fRight(ei) isActive then removeActive(fRight(ei)) else addActive(fRight(ei)) * draw the span from ei to ei+1 with currentActive where addActive adds the fill to the list of currently active fills, removeActive() removes the fill from the active list and currentActive returns the fill AS DEFINED BY THE SORT ORDER from the list of active fills. Note that this does not change anything in the first example above because the list will only contain one entry (besides the empty fill). In the second case however, it will lead to the following sequence: * toggle fLeft(e2) = f(r2) = 'x' - makes fLeft(e2) active - activeList = 'x' * toggle fRight(e2) = f(r3) = 'o' - makes fRight(e2) active - activeList = 'xo' * draw span from e2 to e1 Depending on the sort order between 'x' and 'o' the region will be drawn with either one of the fills. It is significant to note here that the occurence of such a problem is generally only *very* few pixels large (in the above example zero pixels) and will therefore not be visually noticable. In any case, there is a unique decision for the fill to use here and that is what we need if the problem did not happen accidentally (e.g., someone has manually changed one fill of an edge but not the fill of the opposite edge). * toggle fLeft(e1) = f(r1) = '-' - makes fLeft(r1) visible - activeList = 'xo-' [Note: empty fills are a special case. They can be ignored since they sort last and the activeList can return the empty fill if it is itself empty]. * toggle fRight(e1) = f(r2) = 'x' - makes fRight(e1) invisible - activeList = 'o-' * draw span from e2 to e3 Since the active list contains (besides the empty fill) only one fill value this will be used. Fortunately, this is the correct fill because it is the fill we had initially defined for the region r2.An interesting side effect of the above is that there is no such notion as a 'left' or 'right' fill anymore. Another (not-so-nice) side effect is that the entire AET has to be scanned from the beginning even if only the last few edges actually affect the visible region.PS. I need to find a way of clipping the edges for this. More on it later..." ^self error:'Comment only'! !!BalloonEngineBase class methodsFor: 'documentation' stamp: 'ar 11/8/1998 00:06'!a6StuffTODO "This is an unordered list of things to do:BalloonEnginePlugin>>stepToFirstBezierIn:at: 1) Check if reducing maxSteps from 2*deltaY to deltaY brings a *significant* performance improvement. In theory this should make for double step performance but will cost in quality. Might be that the AA stuff will compensate for this - but I'm not really sure.BalloonEngineBase>>dispatchOn:in: 1) Check what dispatches cost most and must be inlined by an #inlinedDispatchOn:in: Probably this will be stepping and eventually wide line stuff but we'll see.BalloonEngineBase 1) Check which variables should become inst vars, if any. This will remove an indirection during memory access and might allow a couple of optimizations by the C compiler.Anti-Aliasing: 1) Check if we can use a weighted 3x3 filter function of the form 1 2 1 2 4 2 1 2 1 Which should be *extremely* nice for fonts (it's sharpening edges). The good thing about the above is that it sums up to 16 (as in the 4x4 case) but I don't know how to keep a history without needing two extra scan lines. 2) Check if we can - somehow - integrate more general filters. 3) Unroll the loops during AA so we can copy and mask aaLevel pixels in each step between start and end. This should speed up filling by a factor of 2-4 (in particular for difficult stuff like radial gradients).Clipping 1) Find a way of clipping edges left of the clip rectangle or at least ignoring most of them after the first scan line. The AET scanning problems discuss the issue but it should be possible to keep the color list between spans (if not empty) and speed up drawing at the very right (such as in the Winnie Pooh example where a lot of stuff is between the left border and the clipping rect. 2) Check if we can determine empty states of the color list and an edge that is longer than anything left of it. This should work in theory but might be relatively expensive to compute." ^self error:'Comment only'! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/24/1998 23:54'!initEdgeConstants: dict "Initialize the edge constants" self initFromSpecArray: #( "Edge primitive types" (GEPrimitiveEdge 2) "External edge - not handled by the GE" (GEPrimitiveWideEdge 3) "Wide external edge" (GEPrimitiveLine 4) "Straight line" (GEPrimitiveWideLine 5) "Wide line" (GEPrimitiveBezier 6) "Quadratic bezier curve" (GEPrimitiveWideBezier 7) "Wide bezier curve" "Special flags" (GEPrimitiveWide 16r01) "Flag determining a wide primitive" (GEPrimitiveWideMask 16rFE) "Mask for clearing the wide flag" (GEEdgeFillsInvalid 16r10000) "Flag determining if left/right fills of an edge are invalid" (GEEdgeClipFlag 16r20000) "Flag determining if this is a clip edge" "General edge state constants" (GEXValue 4) "Current raster x" (GEYValue 5) "Current raster y" (GEZValue 6) "Current raster z" (GENumLines 7) "Number of scan lines remaining" (GEFillIndexLeft 8) "Left fill index" (GEFillIndexRight 9) "Right fill index" (GEBaseEdgeSize 10) "Basic size of each edge" "General fill state constants" (GEBaseFillSize 4) "Basic size of each fill" "General Line state constants" (GLXDirection 10) "Direction of edge (1: left-to-right; -1: right-to-left)" (GLYDirection 11) "Direction of edge (1: top-to-bottom; -1: bottom-to-top)" (GLXIncrement 12) "Increment at each scan line" (GLError 13) "Current error" (GLErrorAdjUp 14) "Error to add at each scan line" (GLErrorAdjDown 15) "Error to subtract on roll-over" "Note: The following entries are only needed before the incremental state is computed. They are therefore aliased to the error values above" (GLEndX 14) "End X of line" (GLEndY 15) "End Y of line" (GLBaseSize 16) "Basic size of each line" "Additional stuff for wide lines" (GLWideFill 16) "Current fill of line" (GLWideWidth 17) "Current width of line" (GLWideEntry 18) "Initial steps" (GLWideExit 19) "Final steps" (GLWideExtent 20) "Target width" (GLWideSize 21) "Size of wide lines" "General Bezier state constants" (GBUpdateData 10) "Incremental update data for beziers" (GBUpdateX 0) "Last computed X value (24.8)" (GBUpdateY 1) "Last computed Y value (24.8)" (GBUpdateDX 2) "Delta X forward difference step (8.24)" (GBUpdateDY 3) "Delta Y forward difference step (8.24)" (GBUpdateDDX 4) "Delta DX forward difference step (8.24)" (GBUpdateDDY 5) "Delta DY forward difference step (8.24)" "Note: The following four entries are only needed before the incremental state is computed. They are therefore aliased to the incremental values above" (GBViaX 12) "via x" (GBViaY 13) "via y" (GBEndX 14) "end x" (GBEndY 15) "end y" (GBBaseSize 16) "Basic size of each bezier. Note: MUST be greater or equal to the size of lines" "Additional stuff for wide beziers" (GBWideFill 16) "Current fill of line" (GBWideWidth 17) "Current width of line" (GBWideEntry 18) "Initial steps" (GBWideExit 19) "Final steps" (GBWideExtent 20) "Target extent" (GBFinalX 21) "Final X value" (GBWideUpdateData 22) "Update data for second curve" (GBWideSize 28) "Size of wide beziers" ) in: dict.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/27/1998 14:19'!initFillConstants: dict "Initialize the fill constants" "BalloonEngineBase initPool" self initFromSpecArray: #( "Fill primitive types" (GEPrimitiveFill 16r100) (GEPrimitiveLinearGradientFill 16r200) (GEPrimitiveRadialGradientFill 16r300) (GEPrimitiveClippedBitmapFill 16r400) (GEPrimitiveRepeatedBitmapFill 16r500) "General fill state constants" (GEBaseFillSize 4) "Basic size of each fill" "Oriented fill constants" (GFOriginX 4) "X origin of fill" (GFOriginY 5) "Y origin of fill" (GFDirectionX 6) "X direction of fill" (GFDirectionY 7) "Y direction of fill" (GFNormalX 8) "X normal of fill" (GFNormalY 9) "Y normal of fill" "Gradient fill constants" (GFRampLength 10) "Length of following color ramp" (GFRampOffset 12) "Offset of first ramp entry" (GGBaseSize 12) "Bitmap fill constants" (GBBitmapWidth 10) "Width of bitmap" (GBBitmapHeight 11) "Height of bitmap" (GBBitmapDepth 12) "Depth of bitmap" (GBBitmapSize 13) "Size of bitmap words" (GBBitmapRaster 14) "Size of raster line" (GBColormapSize 15) "Size of colormap, if any" (GBTileFlag 16) "True if the bitmap is tiled" (GBColormapOffset 18) "Offset of colormap, if any" (GBMBaseSize 18) "Basic size of bitmap fill" ) in: dict.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:26'!initFromSpecArray: specArray in: aDictionary specArray do:[:spec| self initPoolVariable: spec first value: spec last in: aDictionary. ]! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:27'!initPool "BalloonEngineBase initPool" (Smalltalk includesKey: #BalloonEngineConstants) ifFalse:[ Smalltalk declare: #BalloonEngineConstants from: Undeclared. ]. (Smalltalk at: #BalloonEngineConstants) isNil ifTrue:[ (Smalltalk associationAt: #BalloonEngineConstants) value: Dictionary new. ]. self initPool: (Smalltalk at: #BalloonEngineConstants).! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:27'!initPool: aDictionary self initStateConstants: aDictionary. self initWorkBufferConstants: aDictionary. self initPrimitiveConstants: aDictionary. self initEdgeConstants: aDictionary. self initFillConstants: aDictionary. self initializeInstVarNames: BalloonEngine in: aDictionary prefixedBy: 'BE'. self initializeInstVarNames: BalloonEdgeData in: aDictionary prefixedBy: 'ET'. self initializeInstVarNames: BalloonFillData in: aDictionary prefixedBy: 'FT'.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:27'!initPoolFull "BalloonEngineBase initPoolFull" "Move old stuff to Undeclared and re-initialize the receiver" BalloonEngineConstants associationsDo:[:assoc| Undeclared declare: assoc key from: BalloonEngineConstants. ]. self initPool. Undeclared removeUnreferencedKeys.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:27'!initPoolVariable: token value: value in: aDictionary aDictionary declare: token from: Undeclared. (aDictionary associationAt: token) value: value.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:27'!initPrimitiveConstants: dict "Initialize the primitive constants" self initFromSpecArray: #( "Primitive type constants" (GEPrimitiveUnknown 0) (GEPrimitiveEdgeMask 16rFF) (GEPrimitiveFillMask 16rFF00) (GEPrimitiveTypeMask 16rFFFF) "General state constants (Note: could be compressed later)" (GEObjectType 0) "Type of object" (GEObjectLength 1) "Length of object" (GEObjectIndex 2) "Index into external objects" (GEObjectUnused 3) "Currently unused" ) in: dict.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/25/1998 00:25'!initStateConstants: dict "Initialize the state Constants" "BalloonEngineBase initPool" self initFromSpecArray: #( (GEStateUnlocked 0) "Buffer is unlocked and can be modified as wanted" (GEStateAddingFromGET 1) "Adding edges from the GET" (GEStateWaitingForEdge 2) "Waiting for edges added to GET" (GEStateScanningAET 3) "Scanning the active edge table" (GEStateWaitingForFill 4) "Waiting for a fill to mix in during AET scan" (GEStateBlitBuffer 5) "Blt the current scan line" (GEStateUpdateEdges 6) "Update edges to next scan line" (GEStateWaitingChange 7) "Waiting for a changed edge" (GEStateCompleted 8) "Rendering completed" "Error constants" (GErrorNoMoreSpace 1) "No more space in collection" (GErrorBadState 2) "Tried to call a primitive while engine in bad state" (GErrorNeedFlush 3) "Tried to call a primitive that requires flushing before" "Incremental error constants" (GErrorGETEntry 4) "Unknown entry in GET" (GErrorFillEntry 5) "Unknown FILL encountered" (GErrorAETEntry 6) "Unknown entry in AET" ) in: dict.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/25/1998 00:20'!initWorkBufferConstants: dict "Initialize the work buffer constants" "BalloonEngineBase initPool" self initFromSpecArray: #( "General work buffer constants" (GWMagicNumber 16r416E6469) "Magic number" (GWHeaderSize 128) "Size of header" (GWMinimalSize 256) "Minimal size of work buffer" "Header entries" (GWMagicIndex 0) "Index of magic number" (GWSize 1) "Size of full buffer" (GWState 2) "Current state (e.g., locked or not)" "Buffer entries" (GWObjStart 8) "objStart" (GWObjUsed 9) "objUsed" (GWBufferTop 10) "wbTop" (GWGETStart 11) "getStart" (GWGETUsed 12) "getUsed" (GWAETStart 13) "aetStart" (GWAETUsed 14) "aetUsed" "Transform entries" (GWHasEdgeTransform 16) "True if we have an edge transformation" (GWHasColorTransform 17) "True if we have a color transformation" (GWEdgeTransform 18) "2x3 edge transformation" (GWColorTransform 24) "8 word RGBA color transformation" "Span entries" (GWSpanStart 32) "spStart" (GWSpanSize 33) "spSize" (GWSpanEnd 34) "spEnd" (GWSpanEndAA 35) "spEndAA" "Bounds entries" (GWFillMinX 36) "fillMinX" (GWFillMaxX 37) "fillMaxX" (GWFillMinY 38) "fillMinY" (GWFillMaxY 39) "fillMaxY" (GWFillOffsetX 40) "fillOffsetX" (GWFillOffsetY 41) "fillOffsetY" (GWClipMinX 42) (GWClipMaxX 43) (GWClipMinY 44) (GWClipMaxY 45) (GWDestOffsetX 46) (GWDestOffsetY 47) "AA entries" (GWAALevel 48) "aaLevel" (GWAAShift 49) "aaShift" (GWAAColorShift 50) "aaColorShift" (GWAAColorMask 51) "aaColorMask" (GWAAScanMask 52) "aaScanMask" (GWAAHalfPixel 53) "aaHalfPixel" "Misc entries" (GWNeedsFlush 63) "True if the engine may need a flush" (GWStopReason 64) "stopReason" (GWLastExportedEdge 65) "last exported edge" (GWLastExportedFill 66) "last exported fill" (GWLastExportedLeftX 67) "last exported leftX" (GWLastExportedRightX 68) "last exported rightX" (GWClearSpanBuffer 69) "Do we have to clear the span buffer?" (GWPointListFirst 70) "First point list in buffer" (GWPoint1 80) (GWPoint2 82) (GWPoint3 84) (GWPoint4 86) (GWCurrentY 88) "Profile stats" (GWTimeInitializing 90) (GWCountInitializing 91) (GWTimeFinishTest 92) (GWCountFinishTest 93) (GWTimeNextGETEntry 94) (GWCountNextGETEntry 95) (GWTimeAddAETEntry 96) (GWCountAddAETEntry 97) (GWTimeNextFillEntry 98) (GWCountNextFillEntry 99) (GWTimeMergeFill 100) (GWCountMergeFill 101) (GWTimeDisplaySpan 102) (GWCountDisplaySpan 103) (GWTimeNextAETEntry 104) (GWCountNextAETEntry 105) (GWTimeChangeAETEntry 106) (GWCountChangeAETEntry 107) "Bezier stats" (GWBezierMonotonSubdivisions 108) "# of subdivision due to non-monoton beziers" (GWBezierHeightSubdivisions 109) "# of subdivisions due to excessive height" (GWBezierOverflowSubdivisions 110) "# of subdivisions due to possible int overflow" (GWBezierLineConversions 111) "# of beziers converted to lines" (GWHasClipShapes 112) "True if the engine contains clip shapes" (GWCurrentZ 113) "Current z value of primitives" ) in: dict.! !!BalloonEngineBase class methodsFor: 'pool initialization' stamp: 'ar 11/11/1998 22:27'!initializeInstVarNames: aClass in: aDictionary prefixedBy: aString | token value | aClass instVarNames doWithIndex:[:instVarName :index| token _ (aString, instVarName first asUppercase asString, (instVarName copyFrom: 2 to: instVarName size),'Index') asSymbol. value _ index - 1. aDictionary declare: token from: Undeclared. (aDictionary associationAt: token) value: value. ]. token _ (aString, aClass name,'Size') asSymbol. aDictionary declare: token from: Undeclared. (aDictionary associationAt: token) value: aClass instSize.! !!BalloonEnginePlugin methodsFor: 'primitives' stamp: 'ar 5/11/2000 23:07'!primitiveAddBezier | leftFill rightFill viaOop endOop startOop nSegments | self export: true. self inline: false. "Fail if we have the wrong number of arguments" interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. rightFill _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0). leftFill _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 1). viaOop _ interpreterProxy stackObjectValue: 2. endOop _ interpreterProxy stackObjectValue: 3. startOop _ interpreterProxy stackObjectValue: 4. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: (interpreterProxy stackObjectValue: 5) requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. "Make sure the fills are okay" ((self isFillOkay: leftFill) and:[self isFillOkay: rightFill]) ifFalse:[^interpreterProxy primitiveFail]. "Do a quick check if the fillIndices are equal - if so, just ignore it" leftFill = rightFill & false ifTrue:[ ^interpreterProxy pop: 6. "Leave rcvr on stack" ]. self loadPoint: self point1Get from: startOop. self loadPoint: self point2Get from: viaOop. self loadPoint: self point3Get from: endOop. interpreterProxy failed ifTrue:[^0]. self transformPoints: 3. nSegments _ self loadAndSubdivideBezierFrom: self point1Get via: self point2Get to: self point3Get isWide: false. self needAvailableSpace: nSegments * GBBaseSize. engineStopped ifFalse:[ leftFill _ self transformColor: leftFill. rightFill _ self transformColor: rightFill]. engineStopped ifFalse:[ self loadWideBezier: 0 lineFill: 0 leftFill: leftFill rightFill: rightFill n: nSegments. ]. engineStopped ifTrue:[ "Make sure the stack is okay" self wbStackClear. ^interpreterProxy primitiveFail]. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 5. "Leave rcvr on stack" ].! !!BalloonEnginePlugin methodsFor: 'primitives' stamp: 'ar 5/11/2000 23:08'!primitiveAddBezierShape | points lineFill lineWidth fillIndex length isArray segSize nSegments | self export: true. self inline: false. "Fail if we have the wrong number of arguments" interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. lineFill _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0). lineWidth _ interpreterProxy stackIntegerValue: 1. fillIndex _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 2). nSegments _ interpreterProxy stackIntegerValue: 3. points _ interpreterProxy stackObjectValue: 4. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: (interpreterProxy stackObjectValue: 5) requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. "First, do a check if the points look okay" length _ interpreterProxy slotSizeOf: points. (interpreterProxy isWords: points) ifTrue:[ isArray _ false. "Either PointArray or ShortPointArray" (length = (nSegments * 3) or:[length = (nSegments * 6)]) ifFalse:[^interpreterProxy primitiveFail]. ] ifFalse:["Must be Array of points" (interpreterProxy fetchClassOf: points) = interpreterProxy classArray ifFalse:[^interpreterProxy primitiveFail]. length = (nSegments * 3) ifFalse:[^interpreterProxy primitiveFail]. isArray _ true. ]. "Now check that we have some hope to have enough free space. Do this by assuming nPoints boundaries of maximum size, hoping that most of the fills will be colors and many boundaries will be line segments" (lineWidth = 0 or:[lineFill = 0]) ifTrue:[segSize _ GLBaseSize] ifFalse:[segSize _ GLWideSize]. (self needAvailableSpace: segSize * nSegments) ifFalse:[^interpreterProxy primitiveFail]. "Check the fills" ((self isFillOkay: lineFill) and:[self isFillOkay: fillIndex]) ifFalse:[^interpreterProxy primitiveFail]. "Transform colors" lineFill _ self transformColor: lineFill. fillIndex _ self transformColor: fillIndex. engineStopped ifTrue:[^interpreterProxy primitiveFail]. "Check if have anything at all to do" ((lineFill = 0 or:[lineWidth = 0]) and:[fillIndex = 0]) ifTrue:[^interpreterProxy pop: 5]. "Transform the lineWidth" lineWidth = 0 ifFalse:[ lineWidth _ self transformWidth: lineWidth. lineWidth < 1 ifTrue:[lineWidth _ 1]]. "And load the actual shape" isArray ifTrue:[ self loadArrayShape: points nSegments: nSegments fill: fillIndex lineWidth: lineWidth lineFill: lineFill. ] ifFalse:[ self loadShape: (interpreterProxy firstIndexableField: points) nSegments: nSegments fill: fillIndex lineWidth: lineWidth lineFill: lineFill pointsShort: (nSegments * 3 = length)]. engineStopped ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy failed ifFalse:[ self needsFlushPut: 1. self storeEngineStateInto: engine. interpreterProxy pop: 5. "Leave rcvr on stack" ].! !!BalloonEnginePlugin methodsFor: 'primitives' stamp: 'ar 5/11/2000 23:10'!primitiveAddBitmapFill | nrmOop dirOop originOop tileFlag fill xIndex cmOop formOop | self export: true. self inline: false. "Fail if we have the wrong number of arguments" interpreterProxy methodArgumentCount = 7 ifFalse:[^interpreterProxy primitiveFail]. xIndex _ interpreterProxy stackIntegerValue: 0. xIndex <= 0 ifTrue:[^interpreterProxy primitiveFail]. nrmOop _ interpreterProxy stackObjectValue: 1. dirOop _ interpreterProxy stackObjectValue: 2. originOop _ interpreterProxy stackObjectValue: 3. tileFlag _ interpreterProxy booleanValueOf: (interpreterProxy stackValue: 4). tileFlag ifTrue:[tileFlag _ 1] ifFalse:[tileFlag _ 0]. cmOop _ interpreterProxy stackObjectValue: 5. formOop _ interpreterProxy stackObjectValue: 6. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: (interpreterProxy stackObjectValue: 7) requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. self loadPoint: self point1Get from: originOop. self loadPoint: self point2Get from: dirOop. self loadPoint: self point3Get from: nrmOop. interpreterProxy failed ifTrue:[^0]. fill _ self loadBitmapFill: formOop colormap: cmOop tile: tileFlag from: self point1Get along: self point2Get normal: self point3Get xIndex: xIndex-1. engineStopped ifTrue:[ "Make sure the stack is okay" ^interpreterProxy primitiveFail]. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 8. interpreterProxy push: (interpreterProxy positive32BitIntegerFor: fill). ].! !!BalloonEnginePlugin methodsFor: 'primitives' stamp: 'ar 5/11/2000 23:06'!primitiveAddCompressedShape | fillIndexList lineFills lineWidths rightFills leftFills nSegments points pointsShort | self export: true. self inline: false. "Fail if we have the wrong number of arguments" interpreterProxy methodArgumentCount = 7 ifFalse:[^interpreterProxy primitiveFail]. fillIndexList _ interpreterProxy stackObjectValue: 0. lineFills _ interpreterProxy stackObjectValue: 1. lineWidths _ interpreterProxy stackObjectValue: 2. rightFills _ interpreterProxy stackObjectValue: 3. leftFills _ interpreterProxy stackObjectValue: 4. nSegments _ interpreterProxy stackIntegerValue: 5. points _ interpreterProxy stackObjectValue: 6. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: (interpreterProxy stackObjectValue: 7) requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. "First, do a check if the compressed shape is okay" (self checkCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList) ifFalse:[^interpreterProxy primitiveFail]. "Now check that we have some hope to have enough free space. Do this by assuming nSegments boundaries of maximum size, hoping that most of the fills will be colors and many boundaries will be line segments" (self needAvailableSpace: (GBBaseSize max: GLBaseSize) * nSegments) ifFalse:[^interpreterProxy primitiveFail]. "Check if the points are short" pointsShort _ (interpreterProxy slotSizeOf: points) = (nSegments * 3). "Then actually load the compressed shape" self loadCompressedShape: (interpreterProxy firstIndexableField: points) segments: nSegments leftFills: (interpreterProxy firstIndexableField: leftFills) rightFills: (interpreterProxy firstIndexableField: rightFills) lineWidths: (interpreterProxy firstIndexableField: lineWidths) lineFills: (interpreterProxy firstIndexableField: lineFills) fillIndexList: (interpreterProxy firstIndexableField: fillIndexList) pointShort: pointsShort. engineStopped ifTrue:[^interpreterProxy primitiveFail]. interpreterProxy failed ifFalse:[ self needsFlushPut: 1. self storeEngineStateInto: engine. interpreterProxy pop: 7. "Leave rcvr on stack" ].! !!BalloonEnginePlugin methodsFor: 'primitives' stamp: 'ar 5/11/2000 23:13'!primitiveAddGradientFill | isRadial nrmOop dirOop originOop rampOop fill | self export: true. self inline: false. "Fail if we have the wrong number of arguments" interpreterProxy methodArgumentCount = 5 ifFalse:[^interpreterProxy primitiveFail]. isRadial _ interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0). nrmOop _ interpreterProxy stackValue: 1. dirOop _ interpreterProxy stackValue: 2. originOop _ interpreterProxy stackValue: 3. rampOop _ interpreterProxy stackValue: 4. interpreterProxy failed ifTrue:[^nil]. (self quickLoadEngineFrom: (interpreterProxy stackObjectValue: 5) requiredState: GEStateUnlocked) ifFalse:[^interpreterProxy primitiveFail]. self loadPoint: self point1Get from: originOop. self loadPoint: self point2Get from: dirOop. self loadPoint: self point3Get from: nrmOop. interpreterProxy failed ifTrue:[^0]. fill _ self loadGradientFill: rampOop from: self point1Get along: self point2Get normal: self point3Get isRadial: isRadial. engineStopped ifTrue:[ "Make sure the stack is okay" ^interpreterProxy primitiveFail]. interpreterProxy failed ifFalse:[ self storeEngineStateInto: engine. interpreterProxy pop: 6. interpreterProxy push: (interpreterProxy positive32BitIntegerFor: fill). ].! !!BalloonEnginePlugin methodsFor: 'primitives' stamp: 'ar 5/11/2000 23:08'!primitiveAddLine | leftFill rightFill endOop startOop | self export: true. self inline: false. "Fail if we have the wrong number of arguments" interpreterProxy methodArgumentCount = 4 ifFalse:[^interpreterProxy primitiveFail]. rightFill _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0). leftFill _ interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 1). endOop _ interpreterProxy stackObjectValue: 2. startOop _ interpreterProxy stackO